home *** CD-ROM | disk | FTP | other *** search
/ Celestin Apprentice 2 / Apprentice-Release2.iso / Tools / Languages / MacHaskell 2.2 / progs / tutorial / mac-tutorial.lhs next >
Encoding:
Text File  |  1994-09-27  |  79.3 KB  |  2,572 lines  |  [TEXT/ttxt]

  1.  
  2. Page: 0    Introduction
  3.  
  4. This is a programming supplement to `A Gentle Introduction to Haskell'
  5. by Hudak and Fasel.  This supplement augments the tutorial by
  6. providing executable Haskell programs which you can run and
  7. experiment with.  All program fragments in the tutorial are
  8. found here, as well as other examples not included in the tutorial.
  9.  
  10.  
  11. Using This Tutorial
  12.  
  13. You should have a copy of both the `Gentle Introduction' and the
  14. report itself to make full use of this tutorial.  Although the
  15. `Gentle Introduction' is meant to stand by itself, it is often easier
  16. to learn a language through actual use and experimentation than by
  17. reading alone.  Once you finish this introduction, we recommend that
  18. you proceed section by section through the `Gentle Introduction' and
  19. after having read each section go back to this online tutorial.  You
  20. should wait until you have finished the tutorial before attempting to
  21. read the report.
  22.  
  23. This tutorial does not assume any familiarity with Haskell or other
  24. functional languages.  However, knowledge of almost-functional
  25. languages such as ML or Scheme is very useful.  Throughout the
  26. online component of this tutorial, we try to relate Haskell to
  27. other programming languages and clarify the written tutorial through
  28. additional examples and text.
  29.  
  30.  
  31. Organization of the Online Tutorial
  32.  
  33. This online tutorial is divided into a series of pages.  Each page
  34. covers one or more sections in the written tutorial.  You can use
  35. special editor commands to move back and forth through the pages of the
  36. online tutorial.  Each page is a single Haskell program.  Comments in
  37. the program contain the text of the online tutorial.  You can modify
  38. the program freely (this will not change the underlying tutorial
  39. file!) and ask the system to print the value of expressions defined in
  40. the program.
  41.  
  42. At the beginning of each page, the sections covered by the page are
  43. listed.  In addition, the start of each individual section is
  44. marked within each page.
  45.  
  46. To create useful, executable examples of Haskell code, some language
  47. constructs need to be revealed well before they are explained in the
  48. tutorial.  We attempt to point these out when they occur.  Some
  49. small changes have been made to the examples in the written tutorial;
  50. these are usually cosmetic and should be ignored.  Don't feel you have
  51. to understand everything on a page before you move on -- many times
  52. concepts become clearer as you move on and can relate them to other
  53. aspect of the language.
  54.  
  55. Each page of the tutorial defines a set of variables.  Some of
  56. these are named e1, e2, and so on.  These `e' variables are the ones
  57. which are meant for you to evaluate as you go through the tutorial.
  58. Of course you may evaluate any other expressions or variables you wish.
  59.  
  60.  
  61. The Haskell Report
  62.  
  63. While the report is not itself a tutorial on the Haskell language, it
  64. can be an invaluable reference to even a novice user.  A very
  65. important feature of Haskell is the prelude.  The prelude is a
  66. rather large chunk of Haskell code which is implicitly a part of every
  67. Haskell program.  Whenever you see functions used which are not
  68. defined in the current page, these come from the Prelude.  Appendix A
  69. of the report lists the entire Prelude; the index has an entry for
  70. every function in the Prelude.  Looking at the definitions in the
  71. Prelude is sometimes necessary to fully understand the programs in
  72. this tutorial.
  73.  
  74. Another reason to look at the report is to understand the syntax of
  75. Haskell.  Appendix B contains the complete syntax for Haskell.  The
  76. tutorial treats the syntax very informally; the precise details are
  77. found only in the report.
  78.  
  79.  
  80. The Yale Haskell System
  81.  
  82. This version of the tutorial runs under version Y2.1 of Yale Haskell.
  83. The Yale Haskell system is an interactive programming environment for
  84. the Haskell language.  The Macintosh version comes with a built-in 
  85. Emacs-like editor.  Yale Haskell is available free of change via ftp.
  86.  
  87.  
  88. Using the Compiler
  89.  
  90. You can interact with Yale Haskell directly from editor windows.
  91. While many commands are available to the Yale Haskell user, a single
  92. command is the primary means of communicating with the compiler: C-c e. 
  93. (You can also invoke this command as "Eval Expression" from the
  94. "Haskell" menu.)  This command evaluates and prints an expression in
  95. the context of the program on the screen.  Here is what this command
  96. does:
  97.  
  98. a) A dialog box pops up to ask you for the expression to evaluate.
  99.  
  100. b) The "Listener" window pops up onto your screen.
  101.  
  102. c) If the program in the current page of the tutorial has not yet been
  103. compiled or the page has been modified after its most recent
  104. compilation, the entire page is compiled.  This may result in a short delay.
  105.  
  106. d) If there are no errors in the program, the expression entered in
  107. step a) is compiled in the context of the program.  Any value defined
  108. in the current page can be referenced.
  109.  
  110. e) If there are no errors in the expression, its value is printed in
  111. the Listener window.
  112.  
  113. There are also a few other commands you can use.  C-c i interrupts
  114. the Haskell program.  Some tight loops cannot be interrupted; in this
  115. case you will have to kill the Haskell process.    C-c q exits the Haskell
  116. system.
  117.  
  118.  
  119. Editor Commands Used by the Tutorial
  120.  
  121. These commands are specific to the tutorial.  The tutorial is entered
  122. by selecting "Tutorial" from the "Haskell" menu.  To move among
  123. the pages of the tutorial, use
  124.  
  125. C-c C-f  -- go forward 1 page
  126. C-c C-b  -- go back 1 page
  127.  
  128. Each page of the tutorial can be modified without changing the
  129. underlying text of the tutorial.  Changes are not saved as you go
  130. between pages.  To revert a page to its original form use C-c C-l.
  131.  
  132. You can get help regarding the editor commands with C-?.
  133.  
  134.  
  135. You are now ready to start the tutorial.  Start by reading the `Gentle
  136. Introduction' section 1 then proceed through the online tutorial using
  137. C-c C-f to advance to the next page.  You should read about each topic
  138. first before turning to the associated programming example in the
  139. online tutorial.
  140.  
  141. Page: 1   Section 2
  142.  
  143. Section: 2   Values, Types, and Other Goodies
  144.  
  145. This tutorial is written in `literate Haskell'.  This style requires
  146. that all lines containing Haskell code start with `>'; all other
  147. lines are comments and are discarded by the compiler.  Appendix C of
  148. the report defines the syntax of a literate program.  This is the
  149. first line of the Haskell program on this page:
  150.  
  151. > module Test(Bool) where
  152.  
  153. Comments at the end of source code lines start with `--'.  We use
  154. these throughout the tutorial to place explanatory text in the
  155. program. 
  156.  
  157. Remember to use C-c e to evaluate expressions, C-c ? for help.
  158.  
  159. All Haskell programs start with a module declaration, as in the
  160. previous `module Test(Bool) where'.  This can be ignored for now.
  161.  
  162. We will start by defining some identifiers (variables) using equations.
  163. You can print out the value of an identifier by typing C-c e and
  164. typing the name of the identifier you wish to evaluate.  This will
  165. compile the entire program, not just the line with the definition
  166. you want to see.  Not all definitions are very interesting to print out -
  167. by convention, we will use variables e1, e2, ... to denote values that
  168. are interesting to print.
  169.  
  170. We will start with some constants as well as their associated type.
  171. There are two ways to associate a type with a value: a type declaration
  172. and an expression type signature.  Here is an equation and a type
  173. declaration:
  174.  
  175. > e1 :: Int     -- This is a type declaration for the identifier e1
  176. > e1 = 5        -- This is an equation defining e1
  177.  
  178. You can evaluate the expression e1 and watch the system print `5'.
  179.  
  180. Remember that C-c e is prompting for an expression.  Expressions like
  181. e1 or 5 or 1+1 are all valid.  However, `e1 = 5' is a definition,
  182. not an expression.  Trying to evaluate it will result in a syntax error.
  183.  
  184. The type declaration for e1 is not really necessary but we will try to
  185. always provide type declarations for values to help document the program
  186. and to ensure that the system infers the same type we do for an expression.
  187. If you change the value for e1 to `True', the program will no longer
  188. compile due to the type mismatch.
  189.  
  190. We will briefly mention expression type signatures: these are attached to 
  191. expressions instead of identifiers.  Here are equivalent ways to do
  192. the previous definition:
  193.  
  194. > e2 = 5 :: Int
  195. > e3 = (2 :: Int) + (3 :: Int)
  196.  
  197. The :: has very low precedence in expressions and should usually be placed
  198. in parenthesis.
  199.  
  200. There are two completely separate languages in Haskell: an expression
  201. language for values and a type language for type signatures.  The type
  202. language is used only in the type declarations previously described and
  203. declarations of new types, described later.  Haskell uses a
  204. uniform syntax so that values resemble their type signature as much as
  205. possible.  However, you must always be aware of the difference between
  206. type expressions and value expressions.
  207.  
  208. Here are some of the predefined types Haskell provides:
  209.    type           Value Syntax                Type Syntax
  210. Small integers    <digits>                    Int
  211.  
  212. > e4 :: Int
  213. > e4 = 12345
  214.  
  215. Characters        '<character>'               Char
  216.  
  217. > e5 :: Char
  218. > e5 = 'a'
  219.  
  220. Strings           "chars"                     String
  221.  
  222. > e6 :: String
  223. > e6 = "abc"
  224.  
  225. Boolean           True, False                 Bool
  226.  
  227. > e7 :: Bool
  228. > e7 = True
  229.  
  230. Floating point    <digits.digits>             Float
  231.  
  232. > e8 :: Float
  233. > e8 = 123.456
  234.  
  235. Homogeneous list  [<exp1>,<exp2>,...]         [<constituant type>]
  236.  
  237. > e9 :: [Int]
  238. > e9 = [1,2,3]
  239.  
  240. Tuple             (<exp1>,<exp2>,...)         (<exp1-type>,<exp2-type>,...)
  241.  
  242. > e10 :: (Char,Int)
  243. > e10 = ('b',4)
  244.  
  245. Functional        described later             domain type -> range type
  246.  
  247. > succ :: Int -> Int  -- a function which takes an Int argument and returns Int
  248. > succ x = x + 1      -- test this by evaluating `succ 4'
  249.  
  250. Here's a few leftover examples from section 2:
  251.  
  252. > e11 = succ (succ 3)  -- you could also evaluate `succ (succ 3)' directly
  253. >                      -- by entering the entire expression to the C-c e
  254.  
  255. If you want to evaluate something more complex than the `e' variables
  256. defined here, it is better to enter a complex expression, such as
  257. succ (succ 3), directly than to edit a new definition like e10 into
  258. the program.  This is because any change to the program will require
  259. recompilation of the entire page.  The expressions entered to C-c e are
  260. compiled separately (and very quickly!).
  261.  
  262. Uncomment this next line to see a compile time type error.
  263.  
  264. > -- e12 = 'a'+'b'
  265.  
  266. Don't worry about the error message - it will make more sense later.
  267.  
  268. Proceed to the next page using C-c C-f
  269.  
  270. Page: 2   Section 2.1
  271.  
  272. Section: 2.1   Polymorphic Types
  273.  
  274. > module Test(Bool) where
  275.  
  276. The following line allows us to redefine functions in the standard
  277. prelude.  Ignore this for now.
  278.  
  279. > import Prelude hiding (length,head,tail,null)
  280.  
  281. Start with some sample lists to use in test cases:
  282.  
  283. > list1 :: [Int]
  284. > list1 = [1,2,3]
  285. > list2 :: [Char]         -- This is the really a String
  286. > list2 = ['a','b','c']   -- This is the same as "abc"; evaluate list2 and see.
  287. > list3 :: [[a]]          -- The element type of the inner list is unknown
  288. > list3 = [[],[],[],[]]   -- so this list can't be printed
  289. > list4 :: [Int]
  290. > list4 = 1:2:3:4:[]      -- Exactly the same as [1,2,3,4]; print it and see.
  291.  
  292. This is the length function.  You can test it by evaluating expressions
  293. such as `length list1'.  Function application is written by
  294. simple juxtaposition: `f(x)' in other languages would be `f x' in Haskell.
  295.  
  296. > length :: [a] -> Int
  297. > length [] = 0
  298. > length (x:xs) = 1 + length xs
  299.  
  300. Function application has the highest precedence, so 1 + length xs is
  301. parsed as 1 + (length xs).  In general, you have to surround
  302. non-atomic arguments to a function with parens.  This includes
  303. arguments which are also function applications.  For example,
  304. f g x is the function f applied to arguments g and x, similar to
  305. f(g,x) in other languages.  However, f (g x) is f applied to (g x), or
  306. f(g(x)), which means something quite different!  Be especially
  307. careful with infix operators: f x+1 y-2 would be parsed as (f x)+(1 y)-2.
  308. This is also true on the left of the `=': the parens around (x:xs) are
  309. absolutely necessary.  length x:xs would be parsed as (length x):xs.
  310.  
  311. Also be careful with prefix negation, -.  The application `f -1' is
  312. f-1, not f(-1).  Add parens around negative numbers to avoid this
  313. problem.
  314.  
  315. Here are some other list functions:
  316.  
  317. > head :: [a] -> a -- returns the first element in a list (same as car in lisp)
  318. > head (x:xs) = x
  319.  
  320. > tail :: [a] -> [a] -- removes the first element from a list (same as cdr)
  321. > tail (x:xs) = xs
  322.  
  323. > null :: [a] -> Bool
  324. > null [] = True
  325. > null (x:xs) = False
  326.  
  327. > cons :: a -> [a] -> [a]
  328. > cons x xs = x:xs
  329.  
  330. > nil :: [a]
  331. > nil = []
  332.  
  333. Length could be defined using these functions.  This is not good
  334. Haskell style but does illustrate these other list functions.
  335. Haskell programmers feel that the pattern matching style, as used in
  336. the previous version of length, is more natural and readable.
  337.  
  338. > length' :: [a] -> Int   -- Note that ' can be part of a name
  339. > length' x = if null x then 0 else 1 + length' (tail x)
  340.  
  341. A test case for length', cons, and nil
  342.  
  343. > e1 = length' (cons 1 (cons 2 nil))
  344.  
  345. We haven't said anything about errors yet.  Each of the following
  346. examples illustrates a potential runtime or compile time error.  The
  347. compile time error is commented out so that other examples will compile;
  348. you can uncomment them and see what happens.
  349.  
  350. > -- e2 = cons True False   -- Why is this not possible in Haskell?
  351. > e3 = tail (tail ['a'])  -- What happens if you evaluate this?
  352. > e4 = []       -- This is especially mysterious!
  353.  
  354. This last example, e4, is something hard to explain but is often
  355. encountered early by novices.  We haven't explained yet how the system
  356. prints out the expressions you type in - this will wait until later.
  357. However, the problem here is that e4 has the type [a].  The printer for
  358. the list datatype is complaining that it needs to know a specific type
  359. for the list elements even though the list has no elements!  This can
  360. be avoided by giving e4 a type such as [Int].  (To further confuse you,
  361. try giving e4 the type [Char] and see what happens.)
  362.  
  363. Page: 3   Section 2.2
  364.  
  365. Section: 2.2  User-Defined Types
  366.  
  367. > module Test(Bool) where
  368.  
  369. The type Bool is already defined in the Prelude so there is no
  370. need to define it here.
  371.  
  372. > data Color = Red | Green | Blue | Indigo | Violet deriving Text
  373.  
  374. The `deriving Text' is necessary if you want to print a Color value.
  375.  
  376. You can now evaluate these expressions.
  377.  
  378. > e1 :: Color
  379. > e1 = Red
  380. > e2 :: [Color]
  381. > e2 = [Red,Blue]
  382.  
  383. It is very important to keep the expression language and the type
  384. language in Haskell separated.  The data declaration above defines
  385. the type constructor Color.  This is a nullary constructor: it takes no
  386. arguments.  Color is found ONLY in the type language - it can not be
  387. part of an expression.  e1 = Color is meaningless.  (Actually, Color could
  388. be both a data constructor and a type constructor but we'll ignore this
  389. possibility for now).  On the other hand, Red, Blue, and so on are
  390. (nullary) data constructors.  They can appear in expressions and
  391. in patterns (described later).  The declaration e1 :: Blue would also
  392. be meaningless.  Data constructors can be defined ONLY in a data
  393. declaration.
  394.  
  395. In the next example, Point is a type constructor and Pt is a data
  396. constructor.  Point takes one argument and Pt takes two.  A data constructor
  397. like Pt is really just an ordinary function except that it can be used in
  398. a pattern.  Type signatures can not be supplied directly for data
  399. constructors; their typing is completely defined by the data declaration.
  400. However, data constructors have a signature just like any variable:
  401. Pt :: a -> a -> Point a   -- Not valid Haskell syntax
  402. That is, Pt is a function which takes two arguments with the same
  403. arbitrary type and returns a value containing the two argument values.
  404.  
  405. > data Point a = Pt a a   deriving Text
  406.  
  407. > e3 :: Point Float
  408. > e3 = Pt 2.0 3.0
  409. > e4 :: Point Char
  410. > e4 = Pt 'a' 'b'
  411. > e5 :: Point (Point Int)
  412. > e5 = Pt (Pt 1 2) (Pt 3 4)
  413. > -- e6 = Pt 'a' True         -- This is a typing error
  414.  
  415. The individual components of a point do not have names.
  416. Let's jump ahead a little so that we can write functions using these
  417. data types.  Data constructors (Red, Blue, ..., and Pt) can be used in
  418. patterns.  When more than one equation is used to define a function,
  419. pattern matching occurs top down.
  420.  
  421. A function to remove red from a list of colors.
  422.  
  423. > removeRed :: [Color] -> [Color]
  424. > removeRed [] = []
  425. > removeRed (Red:cs) = removeRed cs
  426. > removeRed (c:cs) = c : removeRed cs  -- c cannot be Red at this point
  427.  
  428. > e7 :: [Color]
  429. > e7 = removeRed [Blue,Red,Green,Red]
  430.  
  431. Pattern matching is capable of testing equality with a specific color.
  432.  
  433. All equations defining a function must share a common type.  A
  434. definition such as:
  435.  
  436. foo Red = 1
  437. foo (Pt x y) = x
  438.  
  439. would result in a type error since the argument to foo cannot be both a
  440. Color and a Point.  Similarly, the right hand sides must also share a
  441. common type; a definition such as
  442.  
  443. foo Red = Blue
  444. foo Blue = Pt Red Red
  445.  
  446. would also result in a type error.
  447.  
  448. Here are a couple of functions defined on points.
  449.  
  450. > dist :: Point Float -> Point Float -> Float
  451. > dist (Pt x1 y1) (Pt x2 y2) = sqrt ((x1-x2)^2 + (y1-y2)^2)
  452.  
  453. > midpoint :: Point Float -> Point Float -> Point Float
  454. > midpoint (Pt x1 y1) (Pt x2 y2) = Pt ((x1+x2)/2) ((y1+y2)/2)
  455.  
  456. > p1 :: Point Float
  457. > p1 = Pt 1.0 1.0
  458. > p2 :: Point Float
  459. > p2 = Pt 2.0 2.0
  460.  
  461. > e8 :: Float
  462. > e8 = dist p1 p2
  463. > e9 :: Point Float
  464. > e9 = midpoint p1 p2
  465.  
  466. The only way to take apart a point is to pattern match.
  467. That is, the two values which constitute a point must be extracted
  468. by matching a pattern containing the Pt data constructor.  Much
  469. more will be said about pattern matching later.
  470.  
  471. Haskell prints values in the same syntax used in expressions.  Thus
  472. Pt 1 2 would print as Pt 1 2 (of course, Pt 1 (1+1) would also print
  473. as Pt 1 2).
  474.  
  475. Page: 4  Section 2.3
  476.  
  477. Section: 2.3  Recursive Types
  478.  
  479. > module Test where
  480.  
  481. > data Tree a = Leaf a | Branch (Tree a) (Tree a)    deriving Text
  482.  
  483. The following typings are implied by this declaration.  As before,
  484. this is not valid Haskell syntax.
  485.  
  486. Leaf :: a -> Tree a
  487. Branch :: Tree a -> Tree a -> Tree a
  488.  
  489. > fringe :: Tree a -> [a]
  490. > fringe (Leaf x) = [x]
  491. > fringe (Branch left right) = fringe left ++ fringe right
  492.  
  493. The following trees can be used to test functions:
  494.  
  495. > tree1 :: Tree Int
  496. > tree1 = Branch (Leaf 1) (Branch (Branch (Leaf 2) (Leaf 3)) (Leaf 4))
  497. > tree2 :: Tree Int
  498. > tree2 = Branch (Branch (Leaf 3) (Leaf 1)) (Branch (Leaf 4) (Leaf 1))
  499. > tree3 :: Tree Int
  500. > tree3 = Branch tree1 tree2
  501.  
  502. Try evaluating `fringe tree1' and others.
  503.  
  504. Here's another tree function:
  505.  
  506. > twist :: Tree a -> Tree a
  507. > twist (Branch left right) = Branch right left
  508. > twist x = x        -- This equation only applies to leaves
  509.  
  510. Here's a function which compares two trees to see if they have the
  511. same shape.  Note the signature: the two trees need not contain the
  512. same type of values.
  513.  
  514. > sameShape :: Tree a -> Tree b -> Bool
  515. > sameShape (Leaf x) (Leaf y) = True
  516. > sameShape (Branch l1 r1) (Branch l2 r2) = sameShape l1 l2 && sameShape r1 r2
  517. > sameShape x y = False  -- One is a branch, the other is a leaf
  518.  
  519. The && function is a boolean AND function.
  520.  
  521. The entire pattern on the left hand side must match in order for the 
  522. right hand side to be evaluated.  The first clause requires both 
  523. arguments to be a leaf' otherwise the next equation is tested.  
  524. The last clause will always match: the final x and y match both 
  525. leaves and branches.
  526.  
  527. This compares a tree of integers to a tree of booleans.
  528.  
  529. > e1 = sameShape tree1 (Branch (Leaf True) (Leaf False))
  530.  
  531. Page: 5  Sections 2.4, 2.5, 2.6
  532.  
  533. Section: 2.4  Type Synonyms
  534.  
  535. > module Test(Bool) where
  536.  
  537. Since type synonyms are part of the type language only, it's hard to
  538. write a program which shows what they do.  Essentially, they are like
  539. macros for the type language.  They can be used interchangeably with their
  540. definition:
  541.  
  542. > e1 :: String
  543. > e1 = "abc"
  544. > e2 :: [Char]   -- No different than String
  545. > e2 = e1
  546.  
  547. In the written tutorial the declaration of `Addr' is a data type
  548. declaration, not a synonym declaration.  This shows that the data
  549. type declaration as well as a signature can reference a synonym.
  550.  
  551. Section: 2.5  Built-in Types
  552.  
  553. Tuples are an easy way of grouping a set of data values.  Here are
  554. a few tuples.  Note the consistancy in notation between the values and
  555. types.
  556.  
  557. > e3 :: (Bool,Int)
  558. > e3 = (True,4)
  559. > e4 :: (Char,[Int],Char)
  560. > e4 = ('a',[1,2,3],'b')
  561.  
  562. Here's a function which returns the second component of a 3 tuple.
  563.  
  564. > second :: (a,b,c) -> b
  565. > second (a,b,c) = b
  566.  
  567. Try out `second e3' and `second e4' - what happens?
  568.  
  569. Each different size of tuple is a completely distinct type.  There is
  570. no general way to append two arbitrary tuples or randomly select the
  571. i'th component of an arbitrary tuple.  Here's a function built using
  572. 2-tuples to represent intervals.
  573.  
  574. Use a type synonym to represent homogeneous 2 tuples
  575.  
  576. > type Interval a = (a,a)
  577.  
  578. > containsInterval :: Interval Int -> Interval Int -> Bool
  579. > containsInterval (xmin,xmax) (ymin,ymax) = xmin <= ymin && xmax >= ymax
  580.  
  581. > p1 :: Interval Int
  582. > p1 = (2,3)
  583. > p2 :: Interval Int
  584. > p2 = (1,4)
  585.  
  586. > e5 = containsInterval p1 p2
  587. > e6 = containsInterval p2 p1
  588.  
  589. Here's a type declaration for a type isomorphic to lists:
  590.  
  591. > data List a = Nil | Cons a (List a) deriving Text
  592.  
  593. Except for the notation, this is completely equivalent to ordinary lists
  594. in Haskell.
  595.  
  596. > length' :: List a -> Int
  597. > length' Nil = 0
  598. > length' (Cons x y) = 1 + length' y
  599.  
  600. > e7 = length' (Cons 'a' (Cons 'b' (Cons 'c' Nil)))
  601.  
  602. It is hard to demonstrate much about the `non-specialness' of built-in
  603. types.  However, here is a brief summary:
  604.  
  605. Numbers and characters, such as 1, 2.2, or 'a', are the same as nullary
  606. type constructors.
  607.  
  608. Lists have a special type constructor, [a] instead of List a, and
  609. an odd looking data constructor, [].  The other data constructor, :, is
  610. not `unusual', syntactically speaking.  The notation [x,y] is just
  611. syntax for x:y:[] and "abc" for 'a' : 'b' : 'c' : [].
  612.  
  613. Tuples use a special syntax.  In a type expression, a 2 tuple containing
  614. types a and be would be written (a,b) instead of using a prefix type
  615. constructor such as Tuple2 a b.  This same notation is used to build
  616. tuple values: (1,2) would construct a 2 tuple containing the values 1 and 2.
  617.  
  618.  
  619. Page: 6   Sections 2.5.1, 2.5.2
  620.  
  621. > module Test(Bool) where
  622.  
  623. Section: 2.5.1  List Comprehensions and Arithmetic Sequences
  624.  
  625. Warning: brackets in Haskell are used in three different sorts
  626. of expressions: lists, as in [a,b,c], sequences (distinguished by
  627. the ..), as in [1..2], and list comprehensions (distinguished by the
  628. bar: |), as in [x+1 | x <- xs, x > 1].
  629.  
  630. Before list comprehensions, consider sequences:
  631.  
  632. > e1 :: [Int]
  633. > e1 = [1..10]   -- Step is 1
  634. > e2 :: [Int]
  635. > e2 = [1,3..10] -- Step is 3 - 1
  636. > e3 :: [Int]
  637. > e3 = [1,-1..-10]
  638. > e4 :: [Char]
  639. > e4 = ['a'..'z']   -- This works on chars too
  640.  
  641. We'll avoid infinite sequences like [1..] for now.  If you print one,
  642. use C-c i to interrupt the Haskell program.
  643.  
  644. List comprehensions are very similar to nested loops.  They return a
  645. list of values generated by the expression inside the loop.  The filter
  646. expressions are similar to conditionals in the loop.
  647.  
  648. This function does nothing at all!  It just scans through a list and
  649. copies it into a new one.
  650.  
  651. > doNothing :: [a] -> [a]
  652. > doNothing l = [x | x <- l]
  653.  
  654. Adding a filter to the previous function allows only selected elements to
  655. be generated.  This is similar to what is done in quicksort.
  656.  
  657. > positives :: [Int] -> [Int]
  658. > positives l = [x | x <- l, x > 0]
  659.  
  660. > e5 = positives [2,-4,5,6,-5,3]
  661.  
  662. Now the full quicksort function.
  663.  
  664. > quicksort :: [Char] -> [Char]  -- Use Char just to be different!
  665. > quicksort [] = []
  666. > quicksort (x:xs) = quicksort [y | y <- xs, y <= x] ++
  667. >                    [x] ++
  668. >                    quicksort [y | y <- xs, y > x]
  669.  
  670. > e6 = quicksort "Why use Haskell?"
  671.  
  672. Now for some nested loops.  Each generator, <-, adds another level of
  673. nesting to the loop.  The variable introduced by each generator
  674. can be used in each following generator; all variables can be used in the
  675. generated expression:
  676.  
  677. > e7 :: [(Int,Int)]
  678. > e7 = [(x,y) | x <- [1..5], y <- [x..5]]
  679.  
  680. Now add some guards: (the /= function is `not equal')
  681.  
  682. > e8 :: [(Int,Int)]
  683. > e8 = [(x,y) | x <- [1..7], x /= 5, y <- [x..8] , x*y /= 12]
  684.  
  685. This is the same as the loop: (going to a psuedo Algol notation)
  686. for x := 1 to 7 do
  687.  if x <> 5 then
  688.   for y := x to 8 do
  689.    if x*y <> 12
  690.     generate (x,y)
  691.  
  692. Section: 2.5.2  Strings
  693.  
  694. > e9 = "hello" ++ " world"
  695.  
  696. Page: 7    Sections 3, 3.1
  697.  
  698. > module Test(Bool) where
  699. > import Prelude hiding (map)
  700.  
  701. Section: 3   Functions
  702.  
  703. > add :: Int -> Int -> Int
  704. > add x y = x+y
  705.  
  706. > e1 :: Int
  707. > e1 = add 1 2
  708.  
  709. This Int -> Int is the latter part of the signature of add:
  710.  
  711. add :: Int -> (Int -> Int)
  712.  
  713. > succ :: Int -> Int
  714. > succ = add 1
  715.  
  716. > e2 :: Int
  717. > e2 = succ 3
  718.  
  719. > map :: (a->b) -> [a] -> [b]
  720. > map f [] = []
  721. > map f (x:xs) = f x : (map f xs)
  722.  
  723. > e3 :: [Int]
  724. > e3 = map (add 1) [1,2,3]
  725.  
  726. This next definition is the equivalent to e3
  727.  
  728. > e4 :: [Int]
  729. > e4 = map succ [1,2,3]
  730.  
  731. Heres a more complex example.  Define flist to be a list of functions:
  732.  
  733. > flist :: [Int -> Int]
  734. > flist = map add [1,2,3]
  735.  
  736. This returns a list of functions which add 1, 2, or 3 to their input.
  737. Haskell should print flist as something like
  738.  [<<function>>,<<function>>,<<function>>]
  739.  
  740. Now, define a function which takes a function and returns its value
  741. when applied to the constant 1:
  742.  
  743. > applyTo1 :: (Int -> a) -> a
  744. > applyTo1 f = f 1
  745.  
  746. > e5 :: [Int]
  747. > e5 = map applyTo1 flist  -- Apply each function in flist to 1
  748.  
  749. If you want to look at how the type inference works, figure out how
  750. the signatures of map, applyTo1, and flist combine to yield [Int].
  751.  
  752. Section: 3.1  Lambda Abstractions
  753.  
  754. The symbol \ is like `lambda' in lisp or scheme.
  755.  
  756. Anonymous functions are written as \ arg1 arg2 ... argn -> body
  757. Instead of naming every function, you can code it inline with this
  758. notation:
  759.  
  760. > e6 = map (\f -> f 1) flist
  761.  
  762. Be careful with the syntax here.  \x->\y->x+y parses as
  763.  \ x ->\ y -> x + y.  The ->\ is all one token.  Use spaces!!
  764.  
  765. This is identical to e5 except that the applyTo1 function has no name.
  766.  
  767. Function arguments on the left of an = are the same as lambda on the
  768. right:
  769.  
  770. > add' = \x y -> x+y    -- identical to add
  771. > succ' = \x -> x+1     -- identical to succ
  772.  
  773. As with ordinary function, the parameters to anonymous functions
  774. can be patterns:
  775.  
  776. > e7 :: [Int]
  777. > e7 = map (\(x,y) -> x+y) [(1,2),(3,4),(5,6)]
  778.  
  779. Functions defined by more than one equation, like map, cannot
  780. be converted to anonymous lambda functions quite as easily - a case
  781. statement is also required.  This is discussed later.
  782.  
  783. Page: 8   Sections 3.2, 3.2.1, 3.2.2
  784.  
  785. > module Test(Bool) where
  786.  
  787. > import Prelude hiding ((++),(.))
  788.  
  789. Section: 3.2  Infix operators
  790.  
  791. Haskell has both identifiers, like `x', and operators, like `+'.
  792. These are just two different types of syntax for variables.
  793. However, operators are by default used in infix notation.
  794.  
  795. Briefly, identifiers begin with a letter and may have numbers, _, and '
  796. in them:  x, xyz123, x'', xYz'_12a.  The case of the first letter
  797. distinguishes variables from data constructors (or type variables from
  798. type constructors).  An operator is a string of symbols, where
  799. :!#$%&*+./<=>?@\^| are all symbols.  If the first character is : then
  800. the operator is a data constructor; otherwise it is an ordinary
  801. variable operator.  The - and ~ characters may start a symbol but cannot
  802. be used after the first character.  This allows a*-b to parse as
  803. a * - b instead of a *- b.
  804.  
  805. Operators can be converted to identifiers by enclosing them in parens.
  806. This is required in signature declarations.  Operators can be defined
  807. as well as used in the infix style:
  808.  
  809. > (++) :: [a] -> [a] -> [a]
  810. > [] ++ y = y
  811. > (x:xs) ++ y = x : (xs ++ y)
  812.  
  813. Table 2 (Page 54) of the report is invaluable for sorting out the
  814. precedences of the many predefined infix operators.
  815.  
  816. > e1 = "Foo" ++ "Bar"
  817.  
  818. This is the same function without operator syntax
  819.  
  820. > appendList :: [a] -> [a] -> [a]
  821. > appendList [] y = y
  822. > appendList (x:xs) y = x : appendList xs y
  823.  
  824. > (.) :: (b -> c) -> (a -> b) -> (a -> c)
  825. > f . g = \x -> f (g x)
  826.  
  827. > add1 :: Int -> Int
  828. > add1 x = x+1
  829.  
  830. > e2 = (add1 . add1) 3
  831.  
  832. Section: 3.2.1  Sections
  833.  
  834. Sections are a way of creating unary functions from infix binary
  835. functions.  When a parenthesized expression starts or ends in an
  836. operator, it is a section.  Another definition of add1:
  837.  
  838. > add1' :: Int -> Int
  839. > add1' = (+ 1)
  840.  
  841. > e3 = add1' 4
  842.  
  843. Here are a few section examples:
  844.  
  845. > e4 = map (++ "abc") ["x","y","z"]
  846.  
  847. > e5 = map ("abc" ++) ["x","y","z"]
  848.  
  849.  
  850. Section: 3.2.2  Fixity Declarations
  851.  
  852. We'll avoid any demonstration of fixity declarations.  The Prelude
  853. contains numerous examples.
  854.  
  855. Page: 9  Sections 3.3, 3.4, 3.5
  856.  
  857. > module Test(Bool) where
  858.  
  859. > import Prelude hiding (take,zip)
  860.  
  861. Section: 3.3  Functions are Non-strict
  862.  
  863. Observing lazy evaluation can present difficulties.  The essential
  864. question is `does an expression get evaluated?'.  While in theory using a
  865. non-terminating computation is the way evaluation issues are examined,
  866. we need a more practical approach.  In expressions, Haskell uses `_'
  867. to denote bottom.  Evaluation of `_' will halt execution and print an
  868. informative error message giving the location of the _ which was
  869. evaluated.  While it would seem that `_' is of little use to the
  870. ordinary programmer, this construct is actually quite handy.  Bottom
  871. can be used to create stub functions for program components which have
  872. not been written yet or as a value to insert into data structures
  873. where a data value is required but should never be used.
  874.  
  875. > e1 :: Bool    -- This can be any type at all!
  876. > e1 = _        -- evaluate this and see what happens.
  877.  
  878. > const1 :: a -> Int
  879. > const1 x = 1
  880.  
  881. > e2 :: Int
  882. > e2 = const1 _  -- The bottom is not needed and will thus not be evaluated.
  883.  
  884. Section: 3.4  "Infinite" Data Structures
  885.  
  886. Data structures are constructed lazily.  A constructor like : will not
  887. evaluate its arguments until they are demanded.  All demands arise from
  888. the need to print the result of the computation -- components not needed
  889. to compute the printed result will not be evaluated.
  890.  
  891. > list1 :: [Int]
  892. > list1 = (1:_)
  893.  
  894. > e3 = head list1    -- does not evaluate _
  895. > e4 = tail list1    -- does evaluate _
  896.  
  897. Some infinite data structures.  Don't print these!  If you do, you will
  898. need to interrupt the system (C-c i) or kill the Haskell process.
  899.  
  900. > ones :: [Int]
  901. > ones = 1 : ones
  902.  
  903. > numsFrom :: Int -> [Int]
  904. > numsFrom n = n : numsFrom (n+1)
  905.  
  906. An alternate numsFrom using series notation:
  907.  
  908. > numsFrom' :: Int -> [Int]
  909. > numsFrom' n = [n..]
  910.  
  911. > squares :: [Int]
  912. > squares = map (^2) (numsFrom 0)
  913.  
  914. Before we start printing anything, we need a function to truncate these
  915. infinite lists down to a more manageable size.  The `take' function
  916. extracts the first k elements of a list:
  917.  
  918. > take :: Int -> [a] -> [a]
  919. > take 0 x      = []                 -- two base cases: k = 0
  920. > take k []     = []                 -- or the list is empty
  921. > take k (x:xs) = x : take (k-1) xs
  922.  
  923. now some printable lists:
  924.  
  925. > e5 :: [Int]
  926. > e5 = take 5 ones
  927.  
  928. > e6 :: [Int]
  929. > e6 = take 5 (numsFrom 10)
  930.  
  931. > e7 :: [Int]
  932. > e7 = take 5 (numsFrom' 0)
  933.  
  934. > e8 :: [Int]
  935. > e8 = take 5 squares
  936.  
  937. zip is a function which turns two lists into a list of 2 tuples.  If
  938. the lists are of differing sizes, the result is as long as the
  939. shortest list.
  940.  
  941. > zip (x:xs) (y:ys) = (x,y) : zip xs ys
  942. > zip xs ys = []   -- one of the lists is []
  943.  
  944. > e9 :: [(Int,Int)]
  945. > e9 = zip [1,2,3] [4,5,6]
  946.  
  947. > e10 :: [(Int,Int)]
  948. > e10 = zip [1,2,3] ones
  949.  
  950. > fib :: [Int]
  951. > fib = 1 : 1 : [x+y | (x,y) <- zip fib (tail fib)]
  952.  
  953. > e11 = take 5 fib
  954.  
  955. This can be done without the list comprehension:
  956.  
  957. > fib' :: [Int]
  958. > fib' = 1 : 1 : map (\(x,y) -> x+y) (zip fib (tail fib))
  959.  
  960. This could be written even more cleanly using a map function which
  961. maps a binary function over two lists at once.  This is in the
  962. Prelude and is called zipWith (the name map2 would possibly be clearer!).
  963.  
  964. > fib'' :: [Int]
  965. > fib'' = 1 : 1 : zipWith (+) fib (tail fib)
  966.  
  967. For more examples using infinite structures look in the demo files
  968. that come with Yale Haskell.  Both the pascal program and the
  969. primes program use infinite lists.
  970.  
  971. Section: 3.5  The Error Function
  972.  
  973. Too late - we already used it!  One thing to note is that `_' is not
  974. part of Haskell 1.2 but will be a part of Haskell 1.3 when it is
  975. ready.  Meanwhile, we have added _ to the Yale system in anticipation
  976. of the new report.
  977.  
  978.  
  979. Page: 10   Sections 4, 4.1, 4.2
  980.  
  981. > module Test(Bool) where
  982.  
  983. > import Prelude hiding (take,(^))
  984.  
  985. Section: 4  Case Expressions and Pattern Matching
  986.  
  987. Now for details of pattern matching.  We use [Int] instead of [a]
  988. since the only value of type [a] is [].
  989.  
  990. > contrived :: ([Int], Char, (Int, Float), String, Bool) -> Bool
  991. > contrived ([], 'b', (1, 2.0), "hi", True) = False
  992. > contrived x = True   -- add a second equation to avoid runtime errors
  993.  
  994. > e1 :: Bool
  995. > e1 = contrived ([], 'b', (1, 2.0), "hi", True)
  996. > e2 :: Bool
  997. > e2 = contrived ([1], 'b', (1, 2.0), "hi", True)
  998.  
  999. Contrived just tests its input against a big constant.
  1000.  
  1001. Linearity in pattern matching implies that patterns can only compare
  1002. values with constants.  The following is not valid Haskell:
  1003.  
  1004. member x [] = False
  1005. member x (x:ys) = True      -- Invalid since x appears twice
  1006. member x (y:ys) = member x ys
  1007.  
  1008. The use of `_' in patterns differs from the use of `_' in an
  1009. expression.  In either case `_' can be thought of as a "don't care"
  1010. object; in an expression it means that you don't care what the value
  1011. of the expression is since you never intend to use it.  In a pattern,
  1012. it means that you don't care what value the `_' is being matched
  1013. against.
  1014.  
  1015. > f :: [a] -> [a]
  1016. > f s@(x:xs) = x:s
  1017. > f _ = []
  1018.  
  1019. > e3 = f "abc"
  1020.  
  1021. Another use of _:
  1022.  
  1023. > middle :: (a,b,c) -> b
  1024. > middle (_,x,_) = x
  1025.  
  1026. > e4 :: Char
  1027. > e4 = middle (True, 'a', "123")
  1028.  
  1029. > (^) :: Int -> Int -> Int
  1030. > x ^ 0 = 1
  1031. > x ^ (n+1) = x*(x^n)
  1032.  
  1033. > e5 :: Int
  1034. > e5 = 3^3
  1035. > e6 :: Int
  1036. > e6 = 4^(-2)  -- Notice the behavior of the + pattern on this one
  1037.  
  1038. Section: 4.1  Pattern Matching Semantics
  1039.  
  1040. Here's an extended example to illustrate the left -> right, top -> bottom
  1041. semantics of pattern matching.
  1042.  
  1043. > foo :: (Int,[Int],Int) -> Int
  1044. > foo (1,[2],3)   = 1
  1045. > foo (2,(3:_),3) = 2
  1046. > foo (1,_,3)     = 3
  1047. > foo _           = 4
  1048.  
  1049. > e7 = foo (1,[],3)
  1050. > e8 = foo (1,_,3)
  1051. > e9 = foo (1,1:_,3)
  1052. > e10 = foo (2,_,2)
  1053. > e11 = foo (3,_,_)
  1054.  
  1055. Now add some guards:
  1056.  
  1057. > sign :: Int -> Int
  1058. > sign x | x > 0  = 1
  1059. >        | x == 0 = 0
  1060. >        | x < 0  = -1
  1061.  
  1062. > e12 = sign 3
  1063.  
  1064. The last guard is often `True' to catch all other cases.  The identifier
  1065. `otherwise' is defined as True for use in guards:
  1066.  
  1067. > max' :: Int -> Int -> Int
  1068. > max' x y | x > y      = x
  1069. >          | otherwise  = y
  1070.  
  1071. Guards can refer to any variables bound by pattern matching.  When
  1072. no guard is true, pattern matching resumes at the next equation.  Guards
  1073. may also refer to values bound in an associated where declaration.
  1074.  
  1075.  
  1076. > inOrder :: [Int] -> Bool
  1077. > inOrder (x1:x2:xs) | x1 <= x2 = True
  1078. > inOrder _                     = False
  1079.  
  1080. > e13 = inOrder [1,2,3]
  1081. > e14 = inOrder [2,1]
  1082.  
  1083. Section: 4.2  An Example
  1084.  
  1085. > take :: Int -> [a] -> [a]
  1086. > take 0     _      = []
  1087. > take _     []     = []
  1088. > take (n+1) (x:xs) = x:take n xs
  1089.  
  1090. > take' :: Int -> [a] -> [a]
  1091. > take' _     []     = []
  1092. > take' 0     _      = []
  1093. > take' (n+1) (x:xs) = x:take' n xs
  1094.  
  1095. > e15, e16, e17, e18 :: [Int]
  1096. > e15 = take 0 _
  1097. > e16 = take' 0 _
  1098. > e17 = take _ []
  1099. > e18 = take' _ []
  1100.  
  1101. Page: 11    Sections 4.3, 4.4, 4.5, 4.6
  1102.  
  1103. > module Test(Bool) where
  1104.  
  1105. > import Prelude hiding (take)
  1106.  
  1107. Section: 4.3 Case Expressions
  1108.  
  1109. The function `take' using a case statement instead of multiple equations:
  1110.  
  1111. > take :: Int -> [a] -> [a]
  1112. > take m ys = case (m,ys) of
  1113. >              (0  ,_)    -> []
  1114. >              (_  ,[])   -> []
  1115. >              (n+1,x:xs) -> x : take n xs
  1116.  
  1117. The function take using if then else.  We can also eliminate the n+k
  1118. pattern just for fun.  The original version of take is much easier to read!
  1119.  
  1120. > take' :: Int -> [a] -> [a]
  1121. > take' m ys = if m == 0 then [] else
  1122. >               if null ys then [] else
  1123. >                if m > 0 then head ys : take (m-1) (tail ys)
  1124. >                 else error "m < 0"
  1125.  
  1126. Section: 4.4  Lazy Patterns
  1127.  
  1128. Before the client-server example, here is a contrived example of lazy
  1129. patterns.  The first version will fail to pattern match whenever the
  1130. the first argument is [].  The second version will always pattern
  1131. match initially but x will fail if used when the list is [].
  1132.  
  1133. > nonlazy :: [Int] -> Bool -> [Int]
  1134. > nonlazy (x:xs) isNull  = if isNull then [] else [x]
  1135.  
  1136. > e1 = nonlazy [1,2] False
  1137. > e2 = nonlazy [] True
  1138. > e3 = nonlazy [] False
  1139.  
  1140. This version will never fail the initial pattern match
  1141.  
  1142. > lazy :: [Int] -> Bool -> [Int]
  1143. > lazy ~(x:xs) isNull  = if isNull then [] else [x]
  1144.  
  1145. > e4 = lazy [1,2] False
  1146. > e5 = lazy [] True
  1147. > e6 = lazy [] False
  1148.  
  1149. The server - client example is a little hard to demonstrate.  We'll avoid
  1150. the initial version which loops.  Here is the version with irrefutable
  1151. patterns.
  1152.  
  1153. > type Response = Int
  1154. > type Request = Int
  1155.  
  1156. > client :: Request -> [Response] -> [Request]
  1157. > client init ~(resp:resps) = init : client (next resp) resps
  1158.  
  1159. > server :: [Request] -> [Response]
  1160. > server (req : reqs) = process req : server reqs
  1161.  
  1162. Next maps the response from the previous request onto the next request
  1163.  
  1164. > next :: Response -> Request 
  1165. > next resp = resp
  1166.  
  1167. Process maps a request to a response
  1168.  
  1169. > process :: Request -> Response
  1170. > process req = req+1
  1171.  
  1172. > requests :: [Request]
  1173. > requests = client 0 responses
  1174.  
  1175. > responses :: [Response]
  1176. > responses = server requests
  1177.  
  1178. > e7 = take 5 responses
  1179.  
  1180. The lists of requests and responses are infinite - there is no need to
  1181. check for [] in this program.  These lists correspond to streams in other
  1182. languages.
  1183.  
  1184. Here is fib again:
  1185.  
  1186. > fib :: [Int]
  1187. > fib@(_:tfib) = 1 : 1 : [ a+b | (a,b) <- zip fib tfib]
  1188.  
  1189. > e8 = take 10 fib
  1190.  
  1191. Section: 4.5  Lexical Scoping and Nested Forms
  1192.  
  1193. One thing that is important to note is that the order of the
  1194. definitions in a program, let expression, or where clauses is
  1195. completely arbitrary.  Definitions can be arranged 'top down'
  1196. or `bottom up' without changing the program.
  1197.  
  1198. > e9 = let y = 2 :: Float
  1199. >          f x = (x+y)/y
  1200. >      in f 1 + f 2
  1201.  
  1202. > f :: Int -> Int -> String
  1203. > f x y | y > z  = "y > x^2"
  1204. >       | y == z = "y = x^2"
  1205. >       | y < z  = "y < x^2"
  1206. >   where
  1207. >     z = x*x
  1208.  
  1209. > e10 = f 2 5
  1210. > e11 = f 2 4
  1211.  
  1212. Section: 4.6  Layout
  1213.  
  1214. There's nothing much to demonstrate here.  We have been using layout all
  1215. through the tutorial.  The main thing is to be careful line up the
  1216. first character of each definition.  For example, if you
  1217. change the indentation of the definition of f in e9 you will get a
  1218. parse error.
  1219.  
  1220. Page: 12  Section 5
  1221.  
  1222. > module Test(Bool) where
  1223.  
  1224. > import Prelude hiding (elem)
  1225.  
  1226. Section: 5  Type Classes
  1227.  
  1228. Names in the basic class structure of Haskell cannot be hidden (they are
  1229. in PreludeCore) so we have to modify the names used in the tutorial.
  1230.  
  1231. Here is a new Eq class:
  1232.  
  1233. > class Eq' a where
  1234. >   eq :: a -> a -> Bool
  1235.  
  1236. Now we can define elem using eq from above:
  1237.  
  1238. > elem :: (Eq' a) => a -> [a] -> Bool
  1239. > x `elem` [] = False
  1240. > x `elem` (y:ys) = x `eq` y || x `elem` ys
  1241.  
  1242. Before this is of any use, we need to admit some types to Eq'
  1243.  
  1244. > instance Eq' Int where
  1245. >  x `eq` y = abs (x-y) < 3  -- Let's make this `nearly equal' just for fun
  1246.  
  1247. > instance Eq' Float where
  1248. >  x `eq` y = abs (x-y) < 0.1
  1249.  
  1250. > list1 :: [Int]
  1251. > list1 = [1,5,9,23]
  1252.  
  1253. > list2 :: [Float]
  1254. > list2 = [0.2,5.6,33,12.34]
  1255.  
  1256. > e1 = 2 `elem` list1
  1257. > e2 = 100 `elem` list1
  1258. > e3 = 0.22 `elem` list2
  1259.  
  1260. Watch out!  Integers in Haskell are overloaded - without a type signature
  1261. to designate an integer as an Int, expressions like 3 `eq` 3 will be
  1262. ambiguous.  See 5.5.4 about this problem.
  1263.  
  1264. Now to add the tree type:
  1265.  
  1266. > data Tree a = Leaf a | Branch (Tree a) (Tree a)   deriving Text
  1267.  
  1268. > instance (Eq' a) => Eq' (Tree a) where
  1269. >   (Leaf a)       `eq` (Leaf b)       = a `eq` b
  1270. >   (Branch l1 r1) `eq` (Branch l2 r2) =  (l1 `eq` l2) && (r1 `eq` r2)
  1271. >   _              `eq` _              = False
  1272.  
  1273. > tree1,tree2 :: Tree Int
  1274. > tree1 = Branch (Leaf 1) (Leaf 2)
  1275. > tree2 = Branch (Leaf 2) (Leaf 1)
  1276.  
  1277. > e4 = tree1 `eq` tree2
  1278.  
  1279. Now make a new class with Eq' as a super class:
  1280.  
  1281. > class (Eq' a) => Ord' a where
  1282. >  lt,le :: a -> a -> Bool          -- lt and le are operators in Ord'
  1283. >  x `le` y = x `eq` y || x `lt` y  -- This is a default for le
  1284.  
  1285. The typing of lt & le is 
  1286.  
  1287.  le,lt :: (Ord' a) => a -> a -> Bool
  1288.  
  1289. This is identical to
  1290.  
  1291.  le,lt :: (Eq' a,Ord' a) => a -> a -> Bool
  1292.  
  1293. Make Int an instance of Ord:
  1294.  
  1295. > instance Ord' Int where
  1296. >  x `lt` y = x < y+1
  1297.  
  1298. > i :: Int  -- Avoid ambiguity
  1299. > i = 3
  1300. > e5 :: Bool
  1301. > e5 = i `lt` i
  1302.  
  1303. Some constraints on instance declarations:
  1304.   A program can never have more than one instance declaration for
  1305.     a given combination of data type and class.
  1306.   If a type is declared to be a member of a class, it must also be
  1307.     declared in all superclasses of that class.
  1308.   An instance declaration does not need to supply a method for every
  1309.     operator in the class.  When a method is not supplied in an
  1310.     instance declaration and no default is present in the class
  1311.     declaration, a runtime error occurs if the method is invoked.
  1312.   You must supply the correct context for an instance declaration --
  1313.     this context is not inferred automatically.
  1314.  
  1315. Section: 5.1  Equality and Ordered Classes
  1316. Section: 5.2  Enumeration and Index Classes
  1317.  
  1318. No examples are provided for 5.1 or 5.2.  The standard Prelude contains
  1319. many instance declarations which illustrate the Eq, Ord, and Enum classes.
  1320.  
  1321. Page: 13    Section 5.3
  1322.  
  1323. > module Test(Bool) where
  1324.  
  1325. Section: 5.3   Text and Binary Classes
  1326.  
  1327. This is the slow showTree.  The `show' function is part of the
  1328. Text class and works with all the built-in types.  The context `Text a'
  1329. arises from the call to show for leaf values.
  1330.  
  1331. > data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Text
  1332.  
  1333. > showTree :: (Text a) => Tree a -> String
  1334. > showTree (Leaf x)     = show x
  1335. > showTree (Branch l r) = "<" ++ showTree l ++ "|" ++ showTree r ++ ">"
  1336.  
  1337. > tree1 :: Tree Int
  1338. > tree1 = Branch (Leaf 1) (Branch (Leaf 3) (Leaf 6))
  1339.  
  1340. > e1 = showTree tree1
  1341.  
  1342. Now the improved showTree; shows is already defined for all
  1343. built in types.
  1344.  
  1345. > showsTree  :: Text a => Tree a -> String -> String
  1346. > showsTree (Leaf x) s = shows x s
  1347. > showsTree (Branch l r) s = '<' : showsTree l ('|' : showsTree r ('>' : s))
  1348.  
  1349. > e2 = showsTree tree1 ""
  1350.  
  1351. The final polished version.  ShowS is predefined in the Prelude so we
  1352. don't need it here. 
  1353.  
  1354. > showsTree'  :: Text a => Tree a -> ShowS
  1355. > showsTree' (Leaf x) = shows x
  1356. > showsTree' (Branch l r) = ('<' :) . showsTree' l . ('|' :) .
  1357. >                           showsTree' r . ('>' :)
  1358.  
  1359. > e3 = showsTree' tree1 ""
  1360.  
  1361.  
  1362. Page: 14    This page break is just to keep recompilation from getting too
  1363.             long.  The compiler takes a little longer to compile this
  1364.             page than other pages.
  1365.  
  1366. > module Test(Bool) where
  1367.  
  1368. > data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving Text
  1369.  
  1370. Now for the reading function.  Again, ReadS is predefined and reads works
  1371. for all built-in types.  The generators in the list comprehensions are
  1372. patterns: p <- l binds pattern p to successive elements of l which
  1373. match p.  Elements not matching p are skipped.
  1374.  
  1375. > readsTree :: (Text a) => ReadS (Tree a)
  1376. > readsTree ('<':s)  = [(Branch l r, u) | (l, '|':t) <- readsTree s,
  1377. >                                         (r, '>':u) <- readsTree t ]
  1378. > readsTree s        = [(Leaf x,t)      | (x,t) <- reads s]
  1379.  
  1380. > e4 :: [(Int,String)]
  1381. > e4 = reads "5 golden rings"
  1382.  
  1383. > e5 :: [(Tree Int,String)]
  1384. > e5 = readsTree "<1|<2|3>>"
  1385. > e6 :: [(Tree Int,String)]
  1386. > e6 = readsTree "<1|2"
  1387. > e7 :: [(Tree Int,String)]
  1388. > e7 = readsTree "<1|<<2|3>|<4|5>>> junk at end"
  1389.  
  1390. Before we do the next readTree, let's play with the lex function.
  1391.  
  1392. > e8 :: [(String,String)]
  1393. > e8 = lex "foo bar bletch"
  1394.  
  1395. Here's a function to completely lex a string.  This does not handle
  1396. lexical ambiguity - lex would return more than one possible lexeme
  1397. when an ambiguity is encountered and the patterns used here would not
  1398. match.
  1399.  
  1400. > lexAll :: String -> [String]
  1401. > lexAll s = case lex s of
  1402. >             [("",_)] -> []  -- lex returns an empty token if none is found
  1403. >             [(token,rest)] -> token : lexAll rest
  1404.  
  1405. > e9 = lexAll "lexAll :: String -> [String]"
  1406. > e10 = lexAll "<1|<a|3>>"
  1407.  
  1408. Finally, the complete reader.  This is not sensitive to white space as
  1409. were the previous versions.  When you derive the Text class for a data
  1410. type the reader generated automatically is similar to this in style.
  1411.  
  1412. > readsTree' :: (Text a) => ReadS (Tree a)
  1413. > readsTree' s = [(Branch l r, x) | ("<", t) <- lex s,
  1414. >                   (l, u)   <- readsTree' t,
  1415. >                                   ("|", v) <- lex u,
  1416. >                                   (r, w)   <- readsTree' v,
  1417. >                   (">", x) <- lex w ]
  1418. >                 ++
  1419. >                 [(Leaf x, t)    | (x, t) <- reads s]
  1420.  
  1421. When testing this program, you must make sure the input conforms to
  1422. Haskell lexical syntax.  If you remove spaces between | and < or >
  1423. they will lex as a single token as you should have noticed with e10.
  1424.  
  1425. > e11 :: [(Tree Int,String)]
  1426. > e11 = readsTree' "<1 | <2 | 3> >"
  1427. > e12 :: [(Tree Bool,String)]
  1428. > e12 = readsTree' "<True|False>"
  1429.  
  1430. Finally, here is a simple version of read for trees only:
  1431.  
  1432. > read' :: (Text a) => String -> (Tree a)
  1433. > read' s = case (readsTree' s) of
  1434. >            [(tree,"")] -> tree   -- Only one parse, no junk at end
  1435. >            []          -> error "Couldn't parse tree"
  1436. >            [_]         -> error "Crud after the tree"  -- unread chars at end
  1437. >            _           -> error "Ambiguous parse of tree"
  1438.  
  1439. > e13 :: Tree Int
  1440. > e13 = read' "foo"
  1441. > e14 :: Tree Int
  1442. > e14 = read' "< 1 | < 2 | 3 > >"
  1443. > e15 :: Tree Int
  1444. > e15 = read' "3 xxx"
  1445.  
  1446. Page: 15  Section 5.4
  1447.  
  1448. > module Test(Bool) where
  1449.  
  1450. Section: 5.4  Derived Instances
  1451.  
  1452. We have actually been using the derived Text instances all along for
  1453. printing out trees and other structures we have defined.  The code
  1454. in the tutorial for the Eq and Ord instance of Tree is created
  1455. implicitly by the deriving clause so there is no need to write it
  1456. here.
  1457.  
  1458. > data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving (Eq,Ord,Text)
  1459.  
  1460. Now we can fire up both Eq and Ord functions for trees:
  1461.  
  1462. > tree1, tree2, tree3, tree4 :: Tree Int
  1463. > tree1 = Branch (Leaf 1) (Leaf 3)
  1464. > tree2 = Branch (Leaf 1) (Leaf 5)
  1465. > tree3 = Leaf 4
  1466. > tree4 = Branch (Branch (Leaf 4) (Leaf 3)) (Leaf 5)
  1467.  
  1468. > e1 = tree1 == tree1
  1469. > e2 = tree1 == tree2
  1470. > e3 = tree1 < tree2
  1471.  
  1472. > quicksort :: Ord a => [a] -> [a]
  1473. > quicksort [] = []
  1474. > quicksort (x:xs) = quicksort [y | y <- xs, y <= x] ++
  1475. >                    [x] ++
  1476. >                    quicksort [y | y <- xs, y > x]
  1477.  
  1478. > e4 = quicksort [tree1,tree2,tree3,tree4]
  1479.  
  1480. Now for Enum: 
  1481.  
  1482. > data Day = Sunday | Monday | Tuesday | Wednesday | Thursday |
  1483. >            Friday | Saturday     deriving (Text,Eq,Ord,Enum)
  1484.  
  1485. > e5 = quicksort [Monday,Saturday,Friday,Sunday]
  1486. > e6 = [Wednesday .. Friday]
  1487. > e7 = [Monday, Wednesday ..]
  1488. > e8 = [Saturday, Friday ..]
  1489.  
  1490.  
  1491. Page: 16  Sections 5.5, 5.5.1, 5.5.2, 5.5.3
  1492.  
  1493. > module Test(Bool) where
  1494.  
  1495. Section: 5.5  Numbers
  1496. Section: 5.5.1  Numeric Class Structure
  1497. Section: 5.5.2  Constructed Numbers
  1498.  
  1499. Here's a brief summary of Haskell numeric classes.
  1500.  
  1501. Class Num
  1502.   Most general numeric class.  Has addition, subtraction, multiplication.
  1503.   Integers can be coerced to any instance of Num with fromInteger.
  1504.   All integer constants are in this class.
  1505. Instances: Int, Integer, Float, Double, Ratio a, Complex a
  1506.  
  1507. Class Real
  1508.   This class contains ordered numbers which can be converted to
  1509.   rationals.
  1510. Instances: Int, Integer, Float, Double, Ratio a
  1511.  
  1512. Class Integral
  1513.   This class deals with integer division.  All values in Integral can
  1514.   be mapped onto Integer.
  1515. Instances: Int, Integer
  1516.  
  1517. Class Fractional
  1518.   These are numbers which can be divided.  Any rational number can
  1519.   be converted to a fractional.  Floating point constants are in
  1520.   this class: 1.2 would be 12/10.
  1521. Instances: Float, Double, Ratio a
  1522.  
  1523. Class Floating
  1524.   This class contains all the standard floating point functions such
  1525.   as sqrt and sin.
  1526. Instances: Float, Double, Complex a
  1527.  
  1528. Class RealFrac
  1529.   These values can be rounded to integers and approximated by rationals.
  1530. Instances: Float, Double, Ratio a
  1531.  
  1532. Class RealFloat
  1533.   These are floating point numbers constructed from a fixed precision
  1534.   mantissa and exponent.
  1535. Instances: Float, Double
  1536.  
  1537. There are only a few sensible combinations of the constructed numerics
  1538. with built-in types:
  1539.  Ratio Integer (same as Rational): arbitrary precision rationals
  1540.  Ratio Int: limited precision rationals
  1541.  Complex Float: complex numbers with standard precision components
  1542.  Complex Double: complex numbers with double precision components
  1543.  
  1544.  
  1545. The following function works for arbitrary numerics:
  1546.  
  1547. > fact :: (Num a) => a -> a
  1548. > fact 0 = 1
  1549. > fact n = n*(fact (n-1))
  1550.  
  1551. Note the behavior when applied to different types of numbers:
  1552.  
  1553. > e1 :: Int
  1554. > e1 = fact 6
  1555. > e2 :: Int
  1556. > e2 = fact 20   -- Yale Haskell may not handle overflow gracefully!
  1557. > e3 :: Integer
  1558. > e3 = fact 20
  1559. > e4 :: Rational
  1560. > e4 = fact 6
  1561. > e5 :: Float
  1562. > e5 = fact 6
  1563. > e6 :: Complex Float
  1564. > e6 = fact 6
  1565.  
  1566. Be careful: values like `fact 1.5' will loop.
  1567.  
  1568. As a practical matter, Int operations are much faster than Integer
  1569. operations.  Also, overloaded functions can be much slower than non-
  1570. overloaded functions.  Giving a function like fact a precise typing:
  1571.  
  1572. fact :: Int -> Int
  1573.  
  1574. will yield much faster code.
  1575.  
  1576. In general, numeric expressions work as expected.  Literals are
  1577. a little tricky - they are coerced to the appropriate value.  A
  1578. constant like 1 can be used as ANY numeric type.
  1579.  
  1580. > e7 :: Float
  1581. > e7 = sqrt 2
  1582. > e8 :: Rational
  1583. > e8 = ((4%5) * (1%2)) / (3%4)
  1584. > e9 :: Rational
  1585. > e9 = 2.2 * (3%11) - 1
  1586. > e10 :: Complex Float
  1587. > e10 = (2 * (3:+3)) / (1.1:+2.0 - 1)
  1588. > e11 :: Complex Float
  1589. > e11 = sqrt (-1)
  1590. > e12 :: Integer
  1591. > e12 = numerator (4%2)
  1592. > e13 :: Complex Float
  1593. > e13 = conjugate (4:+5.2)
  1594.  
  1595. A function using pattern matching on complex numbers:
  1596.  
  1597. > mag :: (RealFloat a) => Complex a -> a
  1598. > mag (a:+b) = sqrt (a^2 + b^2)
  1599.  
  1600. > e14 :: Float
  1601. > e14 = mag (1:+1)
  1602.  
  1603. Section: 5.5.3  Numeric Coercions and Overloaded Literals
  1604.  
  1605. The Haskell type system does NOT implicitly coerce values between
  1606. the different numeric types!  Although overloaded constants are 
  1607. coerced when the overloading is resolved, no implicit coercion goes
  1608. on when values of different types are mixed.  For example:
  1609.  
  1610. > f :: Float
  1611. > f = 1.1
  1612. > i1 :: Int
  1613. > i1 = 1
  1614. > i2 :: Integer
  1615. > i2 = 2
  1616.  
  1617. All of these expressions would result in a type error (try them!):
  1618.  
  1619. > -- g = i1 + f
  1620. > -- h = i1 + i2
  1621. > -- i3 :: Int
  1622. > -- i3 = i2
  1623.  
  1624. Appropriate coercions must be introduced by the user to allow
  1625. the mixing of types in arithmetic expressions.
  1626.  
  1627. > e15 :: Float
  1628. > e15 = f + fromIntegral i1
  1629. > e16 :: Integer
  1630. > e16 = fromIntegral i1 + i2
  1631. > e17 :: Int
  1632. > e17 = i1 + fromInteger i2  -- fromIntegral would have worked too.
  1633.  
  1634. Page: 17  Section 5.5.4
  1635.  
  1636. > module Test(Bool) where
  1637.  
  1638. Section: 5.5.4  Default Numeric Types
  1639.  
  1640. Ambiguous contexts arise frequently in numeric expressions.  When an
  1641. expression which produces a value with a general type, such as
  1642. `1' (same as `fromInteger 1'; the type is (Num a) => a), with
  1643. another expression which `consumes' the type, such as `show' or
  1644. `toInteger', ambiguity arises.  This ambiguity can be resolved
  1645. using expression type signatures, but this gets tedious fast!  
  1646. Assigning a type to the top level of an ambiguous expression does
  1647. not help: the ambiguity does not propagate to the top level.
  1648.  
  1649. > e1 :: String -- This type does not influence the type of the argument to show
  1650. > e1 = show 1  -- Does this mean to show an Int or a Float or ...
  1651. > e2 :: String
  1652. > e2 = show (1 :: Float)
  1653. > e3 :: String
  1654. > e3 = show (1 :: Complex Float)
  1655.  
  1656. The reason the first example works is that ambiguous numeric types are
  1657. resolved using defaults.  The defaults in effect here are Int and
  1658. Double.  Since Int `fits' in the expression for e1, Int is used.
  1659. When Int is not valid (due to other context constraints), Double
  1660. will be tried.
  1661.  
  1662. This function defaults the type of the 2's to be Int
  1663.  
  1664. > rms :: (Floating a) => a -> a -> a
  1665. > rms x y = sqrt ((x^2 + y^2) * 0.5)
  1666.  
  1667. The C-c e evaluation used to the Haskell system also makes use of
  1668. defaulting.  When you type an expression, the system creates a
  1669. simple program to print the value of the expression using a function
  1670. like show.  If no type signature for the printed expression is given,
  1671. defaulting may occur.
  1672.  
  1673. One of the reasons for adding type signatures throughout these examples
  1674. is to avoid unexpected defaulting.  Many of the top level signatures are
  1675. required to avoid ambiguity.
  1676.  
  1677. Defaulting can lead to overflow problems when values exceed Int limits.
  1678. Evaluate a very large integer without a type signature to observe this
  1679. (unfortunately this may cause a core dump or other unpleasantness).
  1680.  
  1681. Notice that defaulting applies only to numeric classes.  The
  1682.  
  1683. > --  show (read "xyz")                       -- Try this if you want!
  1684.  
  1685. example uses only class Text so no defaulting occurs.
  1686.  
  1687. Ambiguity also arises with polymorphic types.  As discussed previously,
  1688. expressions like [] have a similar problem.
  1689.  
  1690. > e4 = []   -- Won't print since [] has type [a] and `a' is not known.
  1691.  
  1692. Note the difference: even though the lists have no components, the type
  1693. of component makes a difference in printing.
  1694.  
  1695. > e5 = ([] :: [Int]) 
  1696. > e6 = ([] :: [Char])
  1697.  
  1698. Page: 18   Sections 6, 6.1, 6.2
  1699.  
  1700. Section: 6  Modules
  1701.  
  1702. > module Tree ( Tree(Leaf,Branch), fringe ) where
  1703.  
  1704. Tree(..) would work also
  1705.  
  1706. > data Tree a = Leaf a | Branch (Tree a) (Tree a)   deriving Text
  1707.  
  1708. > fringe :: Tree a -> [a]
  1709. > fringe (Leaf x)             = [x]
  1710. > fringe (Branch left right)  = fringe left ++ fringe right
  1711.  
  1712. The editor interface to Haskell performs evaluation within the
  1713. module containing the cursor.  To evaluate e1 you must place the
  1714. cursor in module Main.
  1715.  
  1716. > module Main (Tree) where
  1717. > import Tree ( Tree(Leaf, Branch), fringe)
  1718. > e1 :: [Int]
  1719. > e1 = fringe (Branch (Leaf 1) (Leaf 2))
  1720.  
  1721. You could also just `import Tree' and get everything from Tree without
  1722. explicitly naming the entities you need.
  1723.  
  1724. This interactive Haskell environment can evaluate expressions in
  1725. any module.  The use of module Main is optional.
  1726.  
  1727. Section: 6.1  Original Names and Renaming
  1728.  
  1729. > module Renamed where
  1730. > import Tree ( Tree(Leaf,Branch), fringe)
  1731. >     renaming (Leaf to Root, Branch to Twig)
  1732.  
  1733. > e2 :: Tree Int
  1734. > e2 = Twig (Root 1) (Root 2)  -- Printing always uses the original names
  1735.  
  1736. Section: 6.2  Interfaces and Implementations
  1737.  
  1738. Yale Haskell allows separate compilation of modules using
  1739. interfaces and unit files.  These are described in the user's guide.
  1740.  
  1741.  
  1742. Page: 19  Sections 6.3, 6.4
  1743.  
  1744. Section: 6.3  Abstract Data Types
  1745.  
  1746. Since TreeADT does not import Tree it can use the name Tree without
  1747. any conflict.  Each module has its own separate namespace.
  1748.  
  1749. > module TreeADT (Tree, leaf, branch, cell, left,
  1750. >                right, isLeaf) where
  1751.  
  1752. > data Tree a = Leaf a | Branch (Tree a) (Tree a)    deriving Text
  1753.  
  1754. > leaf = Leaf
  1755. > branch = Branch
  1756. > cell (Leaf a) = a
  1757. > left (Branch l r) = l
  1758. > right (Branch l r) = r
  1759. > isLeaf (Leaf _) = True
  1760. > isLeaf _        = False
  1761.  
  1762. > module Test where
  1763. > import TreeADT
  1764.  
  1765. Since the constructors for type Tree are hidden, pattern matching
  1766. cannot be used.
  1767.  
  1768. > fringe :: Tree a -> [a]
  1769. > fringe x = if isLeaf x then [cell x]
  1770. >                        else fringe (left x) ++ fringe (right x)
  1771.  
  1772. > e1 :: [Int]
  1773. > e1 = fringe (branch (branch (leaf 3) (leaf 2)) (leaf 1))
  1774.  
  1775. Section: 6.4
  1776.  
  1777. No examples are provided for 6.4.
  1778.  
  1779.  
  1780. Page: 20  Sections 7, 7.1, 7.2, 7.3
  1781.  
  1782. Section: 7  Typing Pitfalls
  1783.  
  1784. Section: 7.1  Let-Bound Polymorphism
  1785.  
  1786. > module Test(e2) where
  1787.  
  1788. > -- f g = (g 'a',g [])    -- This won't typecheck.
  1789.  
  1790. Section: 7.2  Overloaded Numerals
  1791.  
  1792. Overloaded numerics were covered previously - here is one more example.
  1793. sum is a prelude function which sums the elements of a list.
  1794.  
  1795. > average :: (Fractional a) => [a] -> a
  1796. > average xs   = sum xs / fromIntegral (length xs)
  1797.  
  1798. > e1 :: Float   -- Note that e1 would default to Double instead of Int - 
  1799. >               -- this is due to the Fractional context.
  1800. > e1 = average [1,2,3]
  1801.  
  1802. Section: 7.3  The Monomorphism Restriction
  1803.  
  1804. The monomorphism restriction is usually encountered when functions
  1805. are defined without parameters.  If you remove the signature for sum'
  1806. the monomorphism restriction will apply.
  1807. This will generate an error if either:
  1808.   sum' is added to the module export list at the start of this section
  1809.   both sumInt and sumFloat remain in the program.
  1810. If sum' is not exported and all uses of sum' have the same overloading,
  1811. there is no type error.
  1812.  
  1813. > sum' :: (Num a) => [a] -> a
  1814. > sum' = foldl (+) 0         -- foldl reduces a list with a binary function
  1815. >                            -- 0 is the initial value.
  1816.  
  1817. > sumInt :: Int
  1818. > sumInt = sum' [1,2,3]
  1819.  
  1820. > sumFloat :: Float
  1821. > sumFloat = sum' [1,2,3]
  1822.  
  1823. If you use overloaded constants you also may encounter monomorphism:
  1824.  
  1825. > x :: Num a => a
  1826. > x = 1    -- The type of x is Num a => a
  1827. > y :: Int
  1828. > y = x            -- Uses x as an Int
  1829. > z :: Integer
  1830. > z = x          -- Uses x as an Integer.  A monomorphism will occur of the
  1831. >                -- signature for x is removed.
  1832.  
  1833. The error message that this generates is somewhat arbitrary.  When the
  1834. monomorphism restriction applies, the first use of x will determine
  1835. the type and the second will cause the type error.  There is no way to
  1836. be sure which use of x the type checker will encounter first; either
  1837. the `y = x' or the `z = x' may be flagged as the place where the error
  1838. occurs depending on the order in which type checking scans the program.
  1839.  
  1840. Finally, if a value is exported it must not be overloaded unless bound
  1841. by a function binding.  e2 is the only value exported.
  1842.  
  1843. > e2 :: Int  -- Remove this to get an error.  Without this line e1 will
  1844. >            -- be overloaded.
  1845. > e2 = 1
  1846.  
  1847. To prevent annoying error messages about exported monomorphic variables,
  1848. most modules in this tutorial do not implicitly export everything - they
  1849. only export a single value, Bool, which was chosen to keep the export
  1850. list non-empty (a syntactic restriction!).  In Haskell systems without
  1851. the evaluator used here, a module which does not export any names would
  1852. be useless.
  1853.  
  1854. module Test where  -- this would export everything in the module
  1855. module Test(Bool)  -- exports only Bool
  1856. module Test()      -- this is what we really want to do but is not valid.
  1857.  
  1858. Page: 21  Sections 8, 8.1
  1859.  
  1860. > module Test(Bool) where
  1861.  
  1862. Section: 8  Input/Output
  1863. Section: 8.1  Introduction to Continuations
  1864.  
  1865. Simplify f here to be 1/x.
  1866.  
  1867. > data Possibly a  = Ok a | Oops String deriving Text
  1868.  
  1869. > f :: Float -> Possibly Float
  1870. > f x = if x == 0 then Oops "Divide by 0" else Ok (1/x)
  1871.  
  1872. g is a `safe' call to x.  The call to error could be replaced by
  1873. some explicit value like Oops msg -> 0.
  1874.  
  1875. > g x = case f x of
  1876. >         Ok y -> y
  1877. >         Oops msg -> error msg
  1878.    
  1879. > e1 = f 0
  1880. > e2 = g 0
  1881. > e3 = g 1
  1882.  
  1883. Here is the same example using continuations:
  1884.  
  1885. > f' :: Float -> (String -> Float) -> Float
  1886. > f' x c = if x == 0 then c "Divide by 0"
  1887. >                    else 1/x
  1888.  
  1889. > g' x = f' x error   -- calls error on divide by 0
  1890. > g'' x = f' x (\s -> 0) -- returns 0 on divide by 0
  1891.  
  1892. > e4 = g' 0
  1893. > e5 = g'' 0
  1894.  
  1895. Page: 22  Section 8
  1896.  
  1897. > module Test where
  1898.  
  1899. > import Prelude hiding (putStr, getLine)
  1900.  
  1901. Section: 8.1  The I/O Monad
  1902.  
  1903. The I/O monad divides the Haskell world into values and actions.  So far,
  1904. we have only needed to look at values.  To deal with actions, we need
  1905. to introduce a new editor command: C-c r.  We use the term `dialogue'
  1906. to denote an action returning no value, as indicated by the type `IO ()'.
  1907. Instead of printing a value, C-c r runs a dialogue.  (Actually C-c e creates
  1908. an action on the fly and runs it in the same manner as C-c r).  
  1909. As with C-c e you are prompted for an expression; here the type of the
  1910. expression must be IO ().  We use d1,d2,... for dialogues to be
  1911. executed by C-c r.
  1912.  
  1913. In an interactive environment such as this, there is no real need to
  1914. use `main' in module `Main' to designate the dialogue associated with a
  1915. program since C-c r queries for the dialogue to be executed.
  1916. However, many commands such as C-c m make use of this convention.
  1917.  
  1918. The first example is putStr:
  1919.  
  1920. > putStr    :: String -> IO ()
  1921. > putStr s = foldr (>>) (return ()) (map putChar s)
  1922.  
  1923. > d1 = putStr "Hello World"
  1924.  
  1925. Both putStr and getLine are actually in the prelude.
  1926.  
  1927. > getLine :: IO String
  1928. > getLine = getChar >>= (\c ->
  1929. >           if c == '\n' then return ""
  1930. >                        else getLine >>= (\l -> return (c:l)))
  1931.  
  1932. > d2 = putStr "Type Something: " >> getLine >>= (\str ->
  1933. >      putStr "You typed: " >> putStr str >> putStr "\n")
  1934.  
  1935. To experiment with I/O errors, we need to get a bit creative.  Generating
  1936. an error is generally OS specific so instead we use a new
  1937. version of getLine that raises an error when a blank line is entered:
  1938.  
  1939. > getLineErr = getLine >>= (\l ->
  1940. >              if l == "" then failwith EOF
  1941. >                         else return l)
  1942.  
  1943. First, enter a blank line with no active error handler: 
  1944.  
  1945. > d3 = getLineErr >>= putStr
  1946.  
  1947. Now with an error handler:
  1948.  
  1949. > d4 = try getLineErr (\ e -> return (show e)) >>= putStr
  1950.  
  1951. This is the file copier:
  1952.  
  1953. > d5 = getAndOpenFile "Copy from: " ReadMode >>= (\fromHandle ->
  1954. >      getAndOpenFile "Copy to: " WriteMode >>= (\toHandle ->
  1955. >      getContents fromHandle >>= (\contents ->
  1956. >      hPutStr toHandle contents >> close toHandle >> putStr "Done.\n")))
  1957.  
  1958. > getAndOpenFile :: String -> IOMode -> IO Handle
  1959.  
  1960. > getAndOpenFile prompt mode =
  1961. >     putStr prompt >>
  1962. >     getLine >>= (\name ->
  1963. >     try (openFile mode name)
  1964. >         (\err -> putStr ("Cannot open "++ name ++ "\n") >>
  1965. >                  getAndOpenFile prompt mode))
  1966.  
  1967. Finally, an example not in the tutorial.  Reading stdin using getContents
  1968. makes the demands for evaluation of the input stream visible to the user
  1969. since the program will stop for input whenever demand reaches a new line in
  1970. the input stream.
  1971.  
  1972. This reads the entire input stream, breaks it into lines, and hands a list
  1973. of lines to munchInput:
  1974.  
  1975. > d6 = getContents stdin >>= \i -> munchInput (lines i)
  1976.  
  1977. The munchInput function looks at the next line of input.  It prints a prompt
  1978. and then looks at a line of input.  The command `stop' halts execution,
  1979. the command `skip' skips over the next input line, and anything else is
  1980. echoed.
  1981.  
  1982. > munchInput (l:ls) =
  1983. >   putStr "* " >>
  1984. >   case l of
  1985. >    "stop" -> return ()
  1986. >    "skip" -> munchInput (tail ls)
  1987. >    _      -> putStr (l ++ " not understood.\n") >> munchInput ls
  1988.  
  1989. Run this program.  There is a problem with the prompting: it reads the
  1990. input line before the prompt is printed out.  While the case statement would
  1991. be expected to demand a line of input, this demand actually occurs earlier.
  1992. The pattern (l:ls) can only be matched by stripping a line of the input
  1993. stream.  Since this pattern is matched upon entry to munchInput, the input
  1994. demand occurs before the prompt can be printed.
  1995.  
  1996. Change the first line of munchInput to:
  1997.  
  1998. munchInput ~(l:ls) =
  1999.  
  2000. This will allow the prompt to print out before the case statement looks at
  2001. the value of l.  Run the program again.
  2002.  
  2003. Note the behavior when you type "skip".  Again, you need to understand when
  2004. the input will be demanded to figure out why the prompt prints before the
  2005. ignored input line.  Now change this by putting a something in the
  2006. recursive call to munchInput which will look at the line being discarded
  2007. before the recursive call:
  2008.  
  2009.   "skip" -> case ls of (_ : t) -> munchInput t
  2010.  
  2011. This reads the skipped line before the prompt on the recursive call.
  2012.  
  2013. If you find all of this confusing, then the lesson here is that it is probably
  2014. best to avoid reading stdin with getContents.  Using getLine to read a line
  2015. at a time is much easier to understand.  Since getLine is strict with respect
  2016. to the input, there is no way that later demands will suddenly stop execution
  2017. to wait for input.
  2018.  
  2019. For more examples using the I/O system look in the demo programs
  2020. that come with haskell (in $HASKELL/progs/demo) and the report.
  2021.  
  2022. Page: 23  Sections 9, 9.1, 9.2
  2023.  
  2024. > module Test(Bool) where
  2025.  
  2026. Section: 9  Arrays
  2027. Section: 9.1  Index Types
  2028.  
  2029. Arrays are built on the class Ix.  Here are some quick examples of Ix:
  2030.  
  2031. > e1 :: [Int]
  2032. > e1 = range (0,4)
  2033. > e2 :: Int
  2034. > e2 = index (0,4) 2
  2035. > low,high :: (Int,Int)
  2036. > low = (1,1)
  2037. > high = (3,4)
  2038. > e3 = range (low,high)
  2039. > e4 = index (low,high) (3,2)
  2040. > e5 = inRange (low,high) (4,3)
  2041.  
  2042. Section: 9.2  Array Creation
  2043.  
  2044. > squares :: Array Int Int
  2045. > squares = array (1,100) [i := i*i | i <- [1..100]]
  2046.  
  2047. We can also parameterize this a little:
  2048.  
  2049. > squares' :: Int -> Array Int Int
  2050. > squares' n = array (1,n) [i := i*i | i <- [1..n]]
  2051.  
  2052. > e6 :: Int
  2053. > e6 = squares!6
  2054. > e7 :: (Int,Int)
  2055. > e7 = bounds squares
  2056. > e8 :: Array Int Int
  2057. > e8 = squares' 10
  2058.  
  2059. Here is a function which corresponds to `take' for lists.  It takes
  2060. an arbitrary slice out of an array.
  2061.  
  2062. > atake :: (Ix a) => Array a b -> (a,a) -> Array a b
  2063. > atake a (l,u) | inRange (bounds a) l && inRange (bounds a) u =
  2064. >                    array (l,u) [i := a!i | i <- range (l,u)]
  2065. >               | otherwise = error "Subarray out of range"
  2066.  
  2067. > e9 = atake squares (4,8)
  2068.  
  2069. > mkArray :: Ix a => (a -> b) -> (a,a) -> Array a b
  2070. > mkArray f bnds = array bnds [i := f i | i <- range bnds]
  2071.  
  2072. > e10 :: Array Int Int
  2073. > e10 = mkArray (\i -> i*i) (1,10)
  2074.  
  2075. > fibs :: Int -> Array Int Int
  2076. > fibs n = a where
  2077. >             a = array (0,n) ([0 := 1, 1 := 1] ++
  2078. >                              [i := a!(i-1) + a!(i-2) | i <- [2..n]])
  2079.  
  2080. > e11 = atake (fibs 50) (3,10)
  2081.  
  2082. > wavefront :: Int -> Array (Int,Int) Int
  2083. > wavefront n = a where
  2084. >                 a = array ((1,1),(n,n))
  2085. >                      ([(1,j) := 1 | j <- [1..n]] ++
  2086. >                       [(i,1) := 1 | i <- [2..n]] ++
  2087. >                       [(i,j) := a!(i,j-1) + a!(i-1,j-1) + a!(i-1,j)
  2088. >                                   | i <- [2..n], j <- [2..n]])
  2089.  
  2090. > wave = wavefront 20
  2091. > e12 = atake wave ((1,1),(3,3))
  2092. > e13 = atake wave ((3,3),(5,5))
  2093.  
  2094. Here are some errors in array operations:
  2095.  
  2096. > e14 :: Int
  2097. > e14 = wave ! (0,0)  -- Out of bounds
  2098. > arr1 :: Array Int Int
  2099. > arr1 = array (1,10) [1 := 1] -- No value provided for 2..10
  2100. > e15,e16 :: Int
  2101. > e15 = arr1 ! 1  -- works OK
  2102. > e16 = arr1 ! 2  -- undefined by array
  2103.  
  2104. Page: 24  Sections 9.3, 9.4
  2105.  
  2106. > module Test(Bool) where
  2107.  
  2108. Section: 9.3  Accumulation
  2109.  
  2110. > hist :: (Ix a, Integral b) => (a,a) -> [a] -> Array a b
  2111. > hist bnds is = accumArray (+) 0 bnds [i := 1 | i <- is, inRange bnds i]
  2112.  
  2113. > e1 :: Array Char Int
  2114. > e1 = hist ('a','z') "This counts the frequencies of each lowercase letter"
  2115.  
  2116. > decades :: (RealFrac a) => a -> a -> [a] -> Array Int Int
  2117. > decades a b = hist (0,9) . map decade
  2118. >                 where
  2119. >                   decade x = floor ((x-a) * s)
  2120. >                   s = 10 / (b - a)
  2121.  
  2122. > test1 :: [Float]
  2123. > test1 = map sin [0..100]  -- take the sine of the 0 - 100
  2124. > e2 = decades 0 1 test1
  2125.  
  2126. Section: 9.4  Incremental Updates
  2127.  
  2128. > swapRows :: (Ix a, Ix b, Enum b) => a -> a -> Array (a,b) c -> Array (a,b) c
  2129. > swapRows i i' a = a // ([(i,j) := a!(i',j) | j <- [jLo..jHi]] ++
  2130. >             [(i',j) := a!(i,j) | j <- [jLo..jHi]])
  2131. >                where ((iLo,jLo),(iHi,jHi)) = bounds a
  2132.  
  2133. > arr1 :: Array (Int,Int) (Int,Int)
  2134. > arr1 = array ((1,1),(5,5)) [(i,j) := (i,j) | (i,j) <- range ((1,1),(5,5))]
  2135.  
  2136. > e3 = swapRows 2 3 arr1
  2137.  
  2138. Printing the arrays in more readable form makes the results easier
  2139. to view.
  2140.  
  2141. This is a printer for 2d arrays
  2142.  
  2143. > aprint a width = shows (bounds a) . showChar '\n' . showRows lx ly where
  2144. >   showRows r c | r > ux = showChar '\n'
  2145. >   showRows r c | c > uy = showChar '\n' . showRows (r+1) ly
  2146. >   showRows r c = showElt (a!(r,c)) . showRows r (c+1)
  2147. >   showElt e = showString (take width (show e ++ repeat ' ')) . showChar ' '
  2148. >   ((lx,ly),(ux,uy)) = bounds a
  2149.  
  2150. > showArray a w = appendChan stdout (aprint a w "") abort done
  2151.  
  2152. > d1 = showArray e3 6
  2153.  
  2154. > swapRows' :: (Ix a, Ix b, Enum b) => a -> a -> Array (a,b) c -> Array (a,b) c
  2155. > swapRows' i i' a = a // [assoc | j <- [jLo..jHi],
  2156. >                                  assoc <- [(i,j) := a!(i',j),
  2157. >                          (i',j) := a!(i,j)]]
  2158. >                where ((iLo,jLo),(iHi,jHi)) = bounds a
  2159.  
  2160. > d2 = showArray (swapRows' 1 5 arr1) 6
  2161.  
  2162. Page: 25  Section 9.5
  2163.  
  2164. > module Test(Bool) where
  2165.  
  2166. Section: 9.5  An example: Matrix Multiplication
  2167.  
  2168. > aprint a width = shows (bounds a) . showChar '\n' . showRows lx ly where
  2169. >   showRows r c | r > ux = showChar '\n'
  2170. >   showRows r c | c > uy = showChar '\n' . showRows (r+1) ly
  2171. >   showRows r c = showElt (a!(r,c)) . showRows r (c+1)
  2172. >   showElt e = showString (take width (show e ++ repeat ' ')) . showChar ' '
  2173. >   ((lx,ly),(ux,uy)) = bounds a
  2174.  
  2175. > showArray a w = appendChan stdout (aprint a w "") abort done
  2176.  
  2177. > matMult :: (Ix a, Ix b, Ix c, Num d) =>
  2178. >               Array (a,b) d -> Array (b,c) d -> Array (a,c) d
  2179. > matMult x y =
  2180. >   array resultBounds
  2181. >         [(i,j) := sum [x!(i,k) * y!(k,j) | k <- range (lj,uj)]
  2182. >                   | i <- range (li,ui),
  2183. >                     j <- range (lj',uj')]
  2184. >  where
  2185. >     ((li,lj),(ui,uj)) = bounds x
  2186. >     ((li',lj'),(ui',uj')) = bounds y
  2187. >     resultBounds
  2188. >       | (lj,uj)==(li',ui')    =  ((li,lj'),(ui,uj'))
  2189. >       | otherwise             = error "matMult: incompatible bounds"
  2190.  
  2191. > mat1,mat2,mat3,mat4 :: Array (Int,Int) Int
  2192. > mat1 = array ((0,0),(1,1)) [(0,0) := 1,(0,1) := 0,(1,0) := 0,(1,1) := 1]
  2193. > mat2 = array ((0,0),(1,1)) [(0,0) := 1,(0,1) := 1,(1,0) := 1,(1,1) := 1]
  2194. > mat3 = array ((0,0),(1,1)) [(0,0) := 1,(0,1) := 2,(1,0) := 3,(1,1) := 4]
  2195. > mat4 = array ((0,0),(1,2)) [(0,0) := 1,(0,1) := 2,(0,2) := 3,
  2196. >                   (1,0) := 4,(1,1) := 5,(1,2) := 6]
  2197.  
  2198. > d1 = showArray (matMult mat1 mat2) 4
  2199. > d2 = showArray (matMult mat2 mat3) 4
  2200. > d3 = showArray (matMult mat1 mat4) 4
  2201. > d4 = showArray (matMult mat4 mat1) 4
  2202.  
  2203. > matMult' :: (Ix a, Ix b, Ix c, Num d) =>
  2204. >               Array (a,b) d -> Array (b,c) d -> Array (a,c) d
  2205. > matMult' x y =
  2206. >   accumArray (+) 0 ((li,lj'),(ui,uj'))
  2207. >         [(i,j) := x!(i,k) * y!(k,j)
  2208. >                   | i <- range (li,ui),
  2209. >                     j <- range (lj',uj'),
  2210. >                     k <- range (lj,uj)]
  2211. >  where
  2212. >     ((li,lj),(ui,uj)) = bounds x
  2213. >     ((li',lj'),(ui',uj')) = bounds y
  2214. >     resultBounds
  2215. >        | (lj,uj)==(li',ui')    =  ((li,lj'),(ui,uj'))
  2216. >        | otherwise             = error "matMult: incompatible bounds"
  2217.  
  2218. > d5 = showArray (matMult mat1 mat2) 4
  2219. > d6 = showArray (matMult mat2 mat3) 4
  2220.  
  2221. > genMatMul :: (Ix a, Ix b, Ix c) =>
  2222. >               ([f] -> g) -> (d -> e -> f) ->
  2223. >               Array (a,b) d -> Array (b,c) e -> Array (a,c) g
  2224. > genMatMul f g x y =
  2225. >   array ((li,lj'),(ui,uj'))
  2226. >         [(i,j) := f [(x!(i,k)) `g` (y!(k,j)) | k <- range (lj,uj)]
  2227. >                   | i <- range (li,ui),
  2228. >                     j <- range (lj',uj')]
  2229. >  where
  2230. >     ((li,lj),(ui,uj)) = bounds x
  2231. >     ((li',lj'),(ui',uj')) = bounds y
  2232. >     resultBounds
  2233. >          | (lj,uj)==(li',ui')    =  ((li,lj'),(ui,uj'))
  2234. >          | otherwise             = error "matMult: incompatible bounds"
  2235.  
  2236. > d7 = showArray (genMatMul maximum (-) mat2 mat1) 4
  2237. > d8 = showArray (genMatMul and (==) mat1 mat2) 6
  2238. > d9 = showArray (genMatMul and (==) mat1 mat1) 6
  2239.  
  2240. Page: 26     More about Haskell
  2241.  
  2242. This is the end of the tutorial on official Haskell.  If you wish to
  2243. see more examples of Haskell programming, Yale Haskell comes with a
  2244. set of demo programs. These can be found in $HASKELL/progs/demo.  Once
  2245. you have mastered the tutorial, both the report and the user manual
  2246. for Yale Haskell should be understandable.  Many examples of Haskell
  2247. programming can be found in the Prelude.  The directory
  2248. $HASKELL/progs/prelude contains the sources for the Prelude.
  2249.  
  2250. The following pages describe extensions which have been added to the
  2251. Yale system and are not officially a part of the Haskell language.
  2252. Proceed at your own risk!
  2253.  
  2254. We appreciate any comments you have on this tutorial.  Send any comments
  2255. to haskell-requests@cs.yale.edu.
  2256.  
  2257.    The Yale Haskell Group
  2258.  
  2259. Page: 27    Basic Dynamic Typing
  2260.  
  2261. > module Foo(Bool) where
  2262.  
  2263. > import Dynamic
  2264.  
  2265. The next few pages present an overview of the Yale dynamic typing system.
  2266. A tech report describing this approach to dynamic typing is distributed
  2267. in the $HASKELL/doc/dynamic directory.  The prelude files
  2268.  $PRELUDE/PreludeDynamic.hs
  2269.  $PRELUDE/PreludeDeriving.hs
  2270. have quite a bit of documentation in them also.
  2271.  
  2272. Any module using dynamic typing must import Dynamic
  2273.  
  2274. A value of any type can be converted to a single type, Dynamic, using
  2275. the 'toDynamic' construct:
  2276.  
  2277. > e1 = toDynamic True
  2278.  
  2279. > e2 = toDynamic ("abc",False,'z')
  2280.  
  2281. While it uses function calling syntax, toDynamic is not a function
  2282. but a special construct.  Thus `map toDynamic l' would be meaningless.
  2283.  
  2284. When printed, only the signature of the dynamic value is shown.  The
  2285. value inside the dynamic is not printed.
  2286.  
  2287. Dynamic values may be overloaded:
  2288.  
  2289. > e3 = toDynamic 1  -- remember that Haskell adds an implicit 'fromInteger' here
  2290.  
  2291. > e4 = toDynamic (+)
  2292.  
  2293. The inverse of toDynamic is fromDynamic.  This integrates a dynamic
  2294. into the existing type context.
  2295.  
  2296. This function requires that the result of fromDynamic is an Int:
  2297.  
  2298. > f :: Dynamic -> Int
  2299. > f x = fromDynamic x + 1
  2300.  
  2301. > e5 = f (toDynamic 2)
  2302.  
  2303. fromDynamic will fail at runtime if the type of the dynamic is not
  2304. appropriate.  The dynamic type may be more general than the desired
  2305. type (as in e5, since the type of 2 is Num a => a)
  2306.  
  2307. > e6 = f (toDynamic False)  -- This will fail at run time.
  2308.  
  2309. To interrogate the type of a dynamic value, pattern matching can be
  2310. used.  The pattern (p :: Signature) matches a dynamic whose type is
  2311. type is the same as (or can be coereced to) the signature.
  2312.  
  2313. > t (x :: Bool) = if x then "True" else "False"
  2314. > t (x :: Int) = "Int"
  2315. > t (x :: Integer) = "Integer"
  2316. > t _ = "Something else"
  2317.  
  2318. > e7 = t (toDynamic True)
  2319. > e8 = t (toDynamic (1 :: Integer))
  2320. > e9 = t (toDynamic 1)  -- This could match Int or Integer
  2321.  
  2322. More general patterns are also useful:
  2323.  
  2324. > sh (x :: Text a => a) = show x
  2325. > sh _ = "<<Error>>"
  2326.  
  2327. > e10 = sh e1
  2328. > e11 = sh e2
  2329.  
  2330. > data NotInText = NotInText
  2331.  
  2332. > e12 = sh (toDynamic NotInText)
  2333.  
  2334. To round off the special dynamic type operators available, 'typeOf' is
  2335. provided to compute the type of an object.  This returns the 'Signature'
  2336. type which is defined in the module Dynamic.
  2337.  
  2338. > e13 = typeOf foldr
  2339.  
  2340. > e14 = typeOf ((+),"abc",1)
  2341.  
  2342.  
  2343. Page: 28   Operating in the Dynamic domain
  2344.  
  2345. > module Foo(Bool) where
  2346.  
  2347. > import DynamicInternal
  2348.  
  2349. Many operations are supplied for the values and types used by the
  2350. dynamic typing system.
  2351.  
  2352. > dyn1 = toDynamic (1 :: Int)
  2353. > dyn2 = toDynamic "abc"
  2354. > dyn3 = toDynamic (+)
  2355. > dyn4 = toDynamic (error "Evaluating dyn4" :: String)
  2356. > dyn5 = toDynamic (error "Evaluating dyn5")
  2357.  
  2358. The type of a dynamic can be obtained by dType:
  2359. dType :: Dynamic -> Signature
  2360.  
  2361. > e1 = dType dyn1
  2362. > e2 = dType dyn3
  2363.  
  2364. The top level datatype is returned by dDataType:
  2365. dDataType :: Dynamic -> DataType
  2366.  
  2367. > e3 = dDataType dyn1
  2368. > e4 = dDataType dyn2
  2369. > e5 = dDataType dyn4
  2370. > e6 = dDataType dyn5  -- This value has no data type
  2371.  
  2372. Note: the Haskell committee has decided on some official names for
  2373. unnamed types, such as (->) for the function type, [] for the list
  2374. type, and (,) for tuple types.  The dynamic types for these constructs
  2375. do not yet have these names.
  2376.  
  2377. dConstructor returns the data constructor which
  2378. created the value.  This evaluates the data value.
  2379.  
  2380. > e7 = dConstructor dyn1 -- Numerics have a bogus internal constructor
  2381. > e8 = dConstructor dyn2 
  2382. > e9 = dConstructor dyn3 -- Internal constructor for functions
  2383. > e10 = dConstructor dyn4
  2384.  
  2385. The dSlots function take apart a dynamic value:
  2386.  
  2387. > e11 = dSlots dyn2  -- This would be meaningless for the other dynamics
  2388.  
  2389. Finally, dShow converts a dynamic to a string.  This is possible
  2390. even when Text instances are not available for the type.
  2391.  
  2392. > e12 = dShow dyn1
  2393. > e13 = dShow dyn2
  2394. > e14 = map dShow e11
  2395.  
  2396. Function application in the dynamic domain is performed by dApply:
  2397.  dApply :: Dynamic -> [Dynamic] -> Dynamic
  2398.  
  2399. > e15 = dShow (dApply dyn3 [dyn1,dyn1])
  2400. > e16 = dShow (dApply dyn3 [dyn2]) -- A special dynamic type is used for errors.
  2401.  
  2402. Many more dynamic operations are available - see accompanying documentation.
  2403.  
  2404. Page: 29   Existential Types and Dynamic Typing
  2405.  
  2406. > module Foo(Bool) where
  2407.  
  2408. > import Dynamic
  2409.  
  2410. When polymorphism is present, dynamic typing cannot completely capture
  2411. the type of a object.
  2412.  
  2413. > f :: a -> Dynamic
  2414. > f x = toDynamic x
  2415.  
  2416. This function does not have any information about the type of its argument.
  2417. What happens is that a new type is created at runtime every time f is
  2418. called.  These types are called skolem types.
  2419.  
  2420. > e1 = f True
  2421.  
  2422. > e2 = f "abc"
  2423.  
  2424. The type captured by f is basicly useless since this type has no
  2425. 'interesting' properties.  A much more useful function would be
  2426.  
  2427. > f1 :: Num a => a -> Dynamic
  2428. > f1 x = toDynamic x
  2429.  
  2430. > e3 = f1 (1 :: Int)
  2431.  
  2432. The skolem type introduced by f1 will be an instance of Num.
  2433. The signature on f1 is necessary - without it this would have been
  2434. the same as f.
  2435.  
  2436. The following function can be applied to any numeric type, including
  2437. the skolem type found in e3.
  2438.  
  2439. > f2 (x :: Num a => a) = toDynamic (x+2)
  2440.  
  2441. > e4 = f2 e3
  2442.  
  2443. Note that the type in e4 is the same as the type in e3.  Unfortunately
  2444. there is no way to recover the original type, Int.  However, the value
  2445. can be obtained through 'show':
  2446.  
  2447. > e5 = case e4 of (x :: Text a => a) -> show x
  2448.  
  2449. This works because Text is a superclass of Num.
  2450.  
  2451. Warning: skolemization is impure!  Any program that 'looks at' a
  2452. skolem type the wrong way will lose referential transparency.  While
  2453. it is very convenient to have skolem types, they should be used with great
  2454. care.
  2455.  
  2456. More examples of type skolemization can be found in the documentation
  2457. of the dynamic typing system but no further examples will be given here.
  2458.  
  2459. Page: 30    Generalizing Derived Instances with Dynamics
  2460.  
  2461. > module Foo(Bool) where
  2462.  
  2463. > import Dynamic
  2464.  
  2465. One important application of dynamic typing is a generalization of
  2466. derived instances.  In the Haskell report, the various derived instances
  2467. are specified using code templates which are based on datatype 
  2468. declarations. 
  2469. No formal mechanism is provided to add new code templates to Haskell -
  2470. there is no way to add a new derivable instance to the language.
  2471.  
  2472. The Yale compiler provides a mechanism which allows the user to
  2473. introduce new derived instances.  The declaration:
  2474.  
  2475. deriving DI t where
  2476.  instance C t where
  2477.    decl1
  2478.    decl2
  2479.  
  2480. defines a new derived instance, DI, which is expanded by creating an
  2481. instance declaration containing the given decls.  For example, you
  2482. could define a class:
  2483.  
  2484. > class NamedType a where
  2485. >   typeName :: a -> String
  2486.  
  2487. > deriving NamedType a where
  2488. >   instance NamedType a where
  2489. >     typeName x = dDataTypeName (dDataType (toDynamic x))
  2490.  
  2491. > data T1 = T1 deriving NamedType
  2492.  
  2493. > data T2 = T2 deriving NamedType
  2494.  
  2495. > e1 = typeName T1
  2496. > e2 = typeName T2
  2497.  
  2498. All of the standard derived instances propagate their context down to
  2499. the components of a datatype.  For example, for a type to be an instance
  2500. of Eq, all components must also be an instance of Eq.  
  2501.  
  2502. This is a new version of Eq:
  2503.  
  2504. > class MyEq a where
  2505. >   eq :: a -> a -> Bool
  2506.  
  2507. This deriving declaration creates a new derived instance, MyEq, and
  2508. uses dynamic typing to perform the computation of eq.  The context in
  2509. the class declaration, MyEq t, is not applied to the type t but to all
  2510. component types in t.  It may have been cleaner to use something like
  2511.   instance MyEq (subTypes t) => MyEq t
  2512. but this would add extra syntax to the language.
  2513.  
  2514. > deriving MyEq t where
  2515. >   instance MyEq t => MyEq t where
  2516. >     eq x y = dynamicEq (toDynamic x) (toDynamic y)
  2517.  
  2518. This dynamicEq function has different strictness properties from the
  2519. standard Eq class.  It compares right to left instead of left to right.
  2520.  
  2521. > dynamicEq x y = tag x == tag y && foldr (flip (&&)) True slotEqs where
  2522. >   tag x = dConstructorTag (dConstructor x)
  2523. >   slotEqs = zipWith dynEq (dSlots x) (dSlots y)
  2524. >   dynEq x (y :: MyEq a => a) = eq (fromDynamic x) y
  2525.  
  2526. > data Foo = C1 Foo Foo | C2 deriving (Eq,MyEq,Text)
  2527.  
  2528. > e3 = (C1 C2 (C1 C2 C2)) `eq` (C1 C2 (C1 C2 C2))
  2529.  
  2530. > e4 = (C1 C2 (C1 C2 C2)) == (C1 C2 (C1 C2 C2))
  2531.  
  2532. > e5 = (C1 C2 (error "2nd slot")) `eq` (C1 (C1 C2 C2) C2)
  2533.  
  2534. > e6 = (C1 C2 (error "2nd slot")) == (C1 (C1 C2 C2) C2)
  2535.  
  2536. > e7 = (C1 (error "1st slot") C2) `eq` (C1 C2 (C1 C2 C2))
  2537.  
  2538. > e8 = (C1 (error "1st slot") C2) == (C1 C2 (C1 C2 C2))
  2539.  
  2540. The class does not need to match the name of the derived instance.
  2541. For example, an alternative Text instance could be supplied:
  2542.  
  2543. > deriving Text' t where
  2544. >   instance Text t where
  2545. >     showsPrec p x = showDyn (toDynamic x)
  2546.  
  2547. > showDyn x = showString "<<" .
  2548. >             showString (dDataTypeName (dDataType x)) .
  2549. >             showString ">>"
  2550.  
  2551. > data A = B | C deriving Text'
  2552.  
  2553. > e9 = (B,True,[C,B])
  2554.  
  2555. Some other features:
  2556.  
  2557. More than one instance declaration can be supplied in a deriving 
  2558. declaration.
  2559.  
  2560. A context in the deriving declaration can be used to require the presence
  2561. of other instances for the type:
  2562.  
  2563. deriving Eq t => Bar t where
  2564.    instance Ord t where ...
  2565.    
  2566. This deriving will fail if no Eq instance is supplied for the type t.
  2567.  
  2568. The data type can be restricted to enumerated or tuple data types.
  2569. Look into PreludeDeriving for more examples of the deriving declaration.
  2570.  
  2571. This is the end of the tutorial.
  2572.